diff --git a/cardano-api/CHANGELOG.md b/cardano-api/CHANGELOG.md index dc88f8de1..629b72312 100644 --- a/cardano-api/CHANGELOG.md +++ b/cardano-api/CHANGELOG.md @@ -350,7 +350,7 @@ (feature, compatible) [PR 410](https://github.com/IntersectMBO/cardano-api/pull/410) -- Implement Era GADT and UseEra class as an alternative to the existing era handling code +- Implement Era GADT and IsEra class as an alternative to the existing era handling code (feature, compatible) [PR 402](https://github.com/IntersectMBO/cardano-api/pull/402) diff --git a/cardano-api/cardano-api.cabal b/cardano-api/cardano-api.cabal index 1c19c39f7..46e4c0264 100644 --- a/cardano-api/cardano-api.cabal +++ b/cardano-api/cardano-api.cabal @@ -83,6 +83,8 @@ library internal Cardano.Api.Eras.Case Cardano.Api.Eras.Core Cardano.Api.Error + Cardano.Api.Experimental.Eras + Cardano.Api.Experimental.Tx Cardano.Api.Feature Cardano.Api.Fees Cardano.Api.Genesis @@ -123,7 +125,6 @@ library internal Cardano.Api.Orphans Cardano.Api.Pretty Cardano.Api.Protocol - Cardano.Api.Protocol.Version Cardano.Api.ProtocolParameters Cardano.Api.Query Cardano.Api.Query.Expr diff --git a/cardano-api/internal/Cardano/Api/Convenience/Construction.hs b/cardano-api/internal/Cardano/Api/Convenience/Construction.hs index 081f66eb0..d33f04103 100644 --- a/cardano-api/internal/Cardano/Api/Convenience/Construction.hs +++ b/cardano-api/internal/Cardano/Api/Convenience/Construction.hs @@ -17,6 +17,10 @@ where import Cardano.Api.Address import Cardano.Api.Certificate import Cardano.Api.Eon.ShelleyBasedEra +import Cardano.Api.Eon.ShelleyToAlonzoEra +import Cardano.Api.Eras +import Cardano.Api.Experimental.Eras +import Cardano.Api.Experimental.Tx import Cardano.Api.Fees import Cardano.Api.ProtocolParameters import Cardano.Api.Query @@ -29,6 +33,7 @@ import qualified Cardano.Ledger.Coin as L import qualified Cardano.Ledger.Credential as L import qualified Cardano.Ledger.Keys as L +import Data.Bifunctor import qualified Data.List as List import qualified Data.Map.Strict as Map import Data.Set (Set) @@ -72,7 +77,9 @@ constructBalancedTx stakeDelegDeposits drepDelegDeposits shelleyWitSigningKeys = do - BalancedTxBody _ txbody _txBalanceOutput _fee <- + availableEra <- first TxBodyErrorDeprecatedEra $ sbeToEra sbe + + BalancedTxBody _ unsignedTx _txBalanceOutput _fee <- makeTransactionBodyAutoBalance sbe systemStart @@ -86,8 +93,13 @@ constructBalancedTx changeAddr mOverrideWits - let keyWits = map (makeShelleyKeyWitness sbe txbody) shelleyWitSigningKeys - return $ makeSignedTransaction keyWits txbody + let alternateKeyWits = map (makeKeyWitness availableEra unsignedTx) shelleyWitSigningKeys + signedTx = signTx availableEra [] alternateKeyWits unsignedTx + + caseShelleyToAlonzoOrBabbageEraOnwards + (Left . TxBodyErrorDeprecatedEra . DeprecatedEra . shelleyToAlonzoEraToShelleyBasedEra) + (\w -> return $ ShelleyTx sbe $ obtainShimConstraints w signedTx) + sbe data TxInsExistError = TxInsDoNotExist [TxIn] diff --git a/cardano-api/internal/Cardano/Api/Experimental/Eras.hs b/cardano-api/internal/Cardano/Api/Experimental/Eras.hs new file mode 100644 index 000000000..893e96c99 --- /dev/null +++ b/cardano-api/internal/Cardano/Api/Experimental/Eras.hs @@ -0,0 +1,185 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DerivingVia #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE TypeOperators #-} + +-- | This module defines the protocol versions corresponding to the eras in the Cardano blockchain. +module Cardano.Api.Experimental.Eras + ( BabbageEra + , ConwayEra + , Era (..) + , LedgerEra + , IsEra + , ApiEraToLedgerEra + , ExperimentalEraToApiEra + , ApiEraToExperimentalEra + , DeprecatedEra (..) + , EraCommonConstraints + , EraShimConstraints + , obtainCommonConstraints + , obtainShimConstraints + , useEra + , eraToSbe + , babbageEraOnwardsToEra + , sbeToEra + ) +where + +import Cardano.Api.Eon.BabbageEraOnwards +import Cardano.Api.Eon.ShelleyBasedEra (ShelleyBasedEra (..), ShelleyLedgerEra) +import Cardano.Api.Eras.Core (BabbageEra, ConwayEra) +import qualified Cardano.Api.Eras.Core as Api +import qualified Cardano.Api.ReexposeLedger as L +import Cardano.Api.Via.ShowOf + +import qualified Cardano.Ledger.Api as L +import qualified Cardano.Ledger.Babbage as Ledger +import qualified Cardano.Ledger.Conway as Ledger +import qualified Cardano.Ledger.Core as Ledger +import Cardano.Ledger.Hashes +import qualified Cardano.Ledger.SafeHash as L +import qualified Cardano.Ledger.UTxO as L + +import Control.Monad.Error.Class +import Data.Kind +import Prettyprinter + +-- | Users typically interact with the latest features on the mainnet or experiment with features +-- from the upcoming era. Hence, the protocol versions are limited to the current mainnet era +-- and the next era (upcoming era). + +-- Allows us to gradually change the api without breaking things. +-- This will eventually be removed. +type family ExperimentalEraToApiEra era = (r :: Type) | r -> era where + ExperimentalEraToApiEra BabbageEra = Api.BabbageEra + ExperimentalEraToApiEra ConwayEra = Api.ConwayEra + +type family ApiEraToExperimentalEra era = (r :: Type) | r -> era where + ApiEraToExperimentalEra Api.BabbageEra = BabbageEra + ApiEraToExperimentalEra Api.ConwayEra = ConwayEra + +type family LedgerEra era = (r :: Type) | r -> era where + LedgerEra BabbageEra = Ledger.Babbage + LedgerEra ConwayEra = Ledger.Conway + +type family ApiEraToLedgerEra era = (r :: Type) | r -> era where + ApiEraToLedgerEra Api.BabbageEra = Ledger.Babbage + ApiEraToLedgerEra Api.ConwayEra = Ledger.Conway + +-- | Represents the eras in Cardano's blockchain. +-- This type represents eras currently on mainnet and new eras which are +-- in development. +-- +-- After a hardfork, the era from which we hardfork from gets deprecated and +-- after deprecation period, gets removed. During deprecation period, +-- consumers of cardano-api should update their codebase to the mainnet era. +data Era era where + -- | The era currently active on Cardano's mainnet. + BabbageEra :: Era BabbageEra + -- | The upcoming era in development. + ConwayEra :: Era ConwayEra + +deriving instance Show (Era era) + +-- | How to deprecate an era +-- +-- 1. Add DEPRECATED pragma to the era type tag and the era constructor at the same time: +-- @ +-- {-# DEPRECATED BabbageEra "BabbageEra no longer supported, use ConwayEra" #-} +-- data BabbageEra +-- @ +-- +-- 2. Update haddock for the constructor of the deprecated era, mentioning deprecation. +-- +-- @ +-- data Era era where +-- {-# DEPRECATED BabbageEra "BabbageEra no longer supported, use ConwayEra" #-} +-- BabbageEra :: Era BabbageEra +-- -- | The era currently active on Cardano's mainnet. +-- ConwayEra :: Era ConwayEra +-- @ +-- +-- 3. Add new 'IsEra' instance and update the deprecated era instance to produce a compile-time error: +-- @ +-- instance TypeError ('Text "IsEra BabbageEra: Deprecated. Update to ConwayEra") => IsEra BabbageEra where +-- useEra = error "unreachable" +-- +-- instance IsEra ConwayEra where +-- useEra = ConwayEra +-- @ +eraToSbe + :: Era era + -> ShelleyBasedEra (ExperimentalEraToApiEra era) +eraToSbe BabbageEra = ShelleyBasedEraBabbage +eraToSbe ConwayEra = ShelleyBasedEraConway + +newtype DeprecatedEra era + = DeprecatedEra (ShelleyBasedEra era) + deriving Show + +deriving via (ShowOf (DeprecatedEra era)) instance Pretty (DeprecatedEra era) + +sbeToEra + :: MonadError (DeprecatedEra era) m => ShelleyBasedEra era -> m (Era (ApiEraToExperimentalEra era)) +sbeToEra ShelleyBasedEraConway = return ConwayEra +sbeToEra ShelleyBasedEraBabbage = return BabbageEra +sbeToEra e@ShelleyBasedEraAlonzo = throwError $ DeprecatedEra e +sbeToEra e@ShelleyBasedEraMary = throwError $ DeprecatedEra e +sbeToEra e@ShelleyBasedEraAllegra = throwError $ DeprecatedEra e +sbeToEra e@ShelleyBasedEraShelley = throwError $ DeprecatedEra e + +babbageEraOnwardsToEra :: BabbageEraOnwards era -> Era (ApiEraToExperimentalEra era) +babbageEraOnwardsToEra BabbageEraOnwardsBabbage = BabbageEra +babbageEraOnwardsToEra BabbageEraOnwardsConway = ConwayEra + +------------------------------------------------------------------------- + +-- | Type class interface for the 'Era' type. +class IsEra era where + useEra :: Era era + +instance IsEra BabbageEra where + useEra = BabbageEra + +instance IsEra ConwayEra where + useEra = ConwayEra + +obtainShimConstraints + :: BabbageEraOnwards era + -> (EraShimConstraints era => a) + -> a +obtainShimConstraints BabbageEraOnwardsBabbage x = x +obtainShimConstraints BabbageEraOnwardsConway x = x + +-- We need these constraints in order to propagate the new +-- experimental api without changing the existing api +type EraShimConstraints era = + ( LedgerEra (ApiEraToExperimentalEra era) ~ ShelleyLedgerEra era + , ExperimentalEraToApiEra (ApiEraToExperimentalEra era) ~ era + , L.EraTx (ApiEraToLedgerEra era) + ) + +obtainCommonConstraints + :: Era era + -> (EraCommonConstraints era => a) + -> a +obtainCommonConstraints BabbageEra x = x +obtainCommonConstraints ConwayEra x = x + +type EraCommonConstraints era = + ( L.AlonzoEraTx (LedgerEra era) + , L.BabbageEraTxBody (LedgerEra era) + , L.EraTx (LedgerEra era) + , L.EraUTxO (LedgerEra era) + , Ledger.EraCrypto (LedgerEra era) ~ L.StandardCrypto + , ShelleyLedgerEra (ExperimentalEraToApiEra era) ~ LedgerEra era + , L.HashAnnotated (Ledger.TxBody (LedgerEra era)) EraIndependentTxBody L.StandardCrypto + ) diff --git a/cardano-api/internal/Cardano/Api/Experimental/Tx.hs b/cardano-api/internal/Cardano/Api/Experimental/Tx.hs new file mode 100644 index 000000000..865b647f5 --- /dev/null +++ b/cardano-api/internal/Cardano/Api/Experimental/Tx.hs @@ -0,0 +1,204 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} + +module Cardano.Api.Experimental.Tx + ( UnsignedTx (..) + , UnsignedTxError (..) + , makeUnsignedTx + , makeKeyWitness + , signTx + , convertTxBodyToUnsignedTx + , hashTxBody + ) +where + +import Cardano.Api.Eon.ShelleyBasedEra +import Cardano.Api.Eras.Case +import Cardano.Api.Experimental.Eras +import Cardano.Api.Feature +import Cardano.Api.ReexposeLedger (StrictMaybe (..), maybeToStrictMaybe) +import qualified Cardano.Api.ReexposeLedger as L +import Cardano.Api.Tx.Body +import Cardano.Api.Tx.Sign + +import qualified Cardano.Ledger.Alonzo.TxBody as L +import qualified Cardano.Ledger.Api as L +import qualified Cardano.Ledger.Babbage as Ledger +import qualified Cardano.Ledger.Conway as Ledger +import qualified Cardano.Ledger.Conway.TxBody as L +import qualified Cardano.Ledger.Core as Ledger +import Cardano.Ledger.Hashes +import qualified Cardano.Ledger.Keys as L +import qualified Cardano.Ledger.SafeHash as L + +import qualified Data.Map.Strict as Map +import qualified Data.Set as Set +import Lens.Micro + +-- | A transaction that can contain everything +-- except key witnesses +newtype UnsignedTx era + = UnsignedTx (Ledger.Tx (LedgerEra era)) + +instance IsEra era => Show (UnsignedTx era) where + showsPrec p (UnsignedTx tx) = case useEra @era of + BabbageEra -> showsPrec p (tx :: Ledger.Tx Ledger.Babbage) + ConwayEra -> showsPrec p (tx :: Ledger.Tx Ledger.Conway) + +newtype UnsignedTxError + = UnsignedTxError TxBodyError + +makeUnsignedTx + :: Era era + -> TxBodyContent BuildTx (ExperimentalEraToApiEra era) + -> Either TxBodyError (UnsignedTx era) +makeUnsignedTx era bc = obtainCommonConstraints era $ do + let sbe = eraToSbe era + + -- cardano-api types + let apiTxOuts = txOuts bc + apiScriptWitnesses = collectTxBodyScriptWitnesses sbe bc + apiScriptValidity = txScriptValidity bc + apiMintValue = txMintValue bc + apiProtocolParameters = txProtocolParams bc + apiCollateralTxIns = txInsCollateral bc + apiReferenceInputs = txInsReference bc + apiExtraKeyWitnesses = txExtraKeyWits bc + apiReturnCollateral = txReturnCollateral bc + apiTotalCollateral = txTotalCollateral bc + + -- Ledger types + txins = convTxIns $ txIns bc + collTxIns = convCollateralTxIns apiCollateralTxIns + refTxIns = convReferenceInputs apiReferenceInputs + outs = convTxOuts sbe apiTxOuts + fee = convTransactionFee sbe $ txFee bc + withdrawals = convWithdrawals $ txWithdrawals bc + returnCollateral = convReturnCollateral sbe apiReturnCollateral + totalCollateral = convTotalCollateral apiTotalCollateral + certs = convCertificates sbe $ txCertificates bc + txAuxData = toAuxiliaryData sbe (txMetadata bc) (txAuxScripts bc) + scripts = convScripts apiScriptWitnesses + languages = convLanguages apiScriptWitnesses + sData = convScriptData sbe apiTxOuts apiScriptWitnesses + + let setMint = convMintValue apiMintValue + setReqSignerHashes = convExtraKeyWitnesses apiExtraKeyWitnesses + ledgerTxBody = + L.mkBasicTxBody + & L.inputsTxBodyL .~ txins + & L.collateralInputsTxBodyL .~ collTxIns + & L.referenceInputsTxBodyL .~ refTxIns + & L.outputsTxBodyL .~ outs + & L.totalCollateralTxBodyL .~ totalCollateral + & L.collateralReturnTxBodyL .~ returnCollateral + & L.feeTxBodyL .~ fee + & L.vldtTxBodyL . L.invalidBeforeL .~ convValidityLowerBound (txValidityLowerBound bc) + & L.vldtTxBodyL . L.invalidHereAfterL .~ convValidityUpperBound sbe (txValidityUpperBound bc) + & L.reqSignerHashesTxBodyL .~ setReqSignerHashes + & L.scriptIntegrityHashTxBodyL .~ getScriptIntegrityHash apiProtocolParameters languages sData + & L.withdrawalsTxBodyL .~ withdrawals + & L.certsTxBodyL .~ certs + & L.mintTxBodyL .~ setMint + & L.auxDataHashTxBodyL .~ maybe SNothing (SJust . Ledger.hashTxAuxData) txAuxData + + scriptWitnesses = + L.mkBasicTxWits + & L.scriptTxWitsL + .~ Map.fromList + [ (L.hashScript sw, sw) + | sw <- scripts + ] + eraSpecificTxBody <- eraSpecificLedgerTxBody era ledgerTxBody bc + + return . UnsignedTx $ + L.mkBasicTx eraSpecificTxBody + & L.witsTxL .~ scriptWitnesses + & L.auxDataTxL .~ maybeToStrictMaybe (toAuxiliaryData sbe (txMetadata bc) (txAuxScripts bc)) + & L.isValidTxL .~ txScriptValidityToIsValid apiScriptValidity + +eraSpecificLedgerTxBody + :: Era era + -> Ledger.TxBody (LedgerEra era) + -> TxBodyContent BuildTx (ExperimentalEraToApiEra era) + -> Either TxBodyError (Ledger.TxBody (LedgerEra era)) +eraSpecificLedgerTxBody BabbageEra ledgerbody bc = do + let sbe = eraToSbe BabbageEra + + setUpdateProposal <- convTxUpdateProposal sbe (txUpdateProposal bc) + + return $ ledgerbody & L.updateTxBodyL .~ setUpdateProposal +eraSpecificLedgerTxBody ConwayEra ledgerbody bc = + let propProcedures = txProposalProcedures bc + voteProcedures = txVotingProcedures bc + treasuryDonation = txTreasuryDonation bc + currentTresuryValue = txCurrentTreasuryValue bc + in return $ + ledgerbody + & L.proposalProceduresTxBodyL + .~ convProposalProcedures (maybe TxProposalProceduresNone unFeatured propProcedures) + & L.votingProceduresTxBodyL + .~ convVotingProcedures (maybe TxVotingProceduresNone unFeatured voteProcedures) + & L.treasuryDonationTxBodyL .~ maybe (L.Coin 0) unFeatured treasuryDonation + & L.currentTreasuryValueTxBodyL + .~ L.maybeToStrictMaybe (maybe (Just $ L.Coin 0) unFeatured currentTresuryValue) + +hashTxBody + :: L.HashAnnotated (Ledger.TxBody era) EraIndependentTxBody L.StandardCrypto + => L.TxBody era -> L.Hash L.StandardCrypto EraIndependentTxBody +hashTxBody = L.extractHash @L.StandardCrypto . L.hashAnnotated + +makeKeyWitness + :: Era era + -> UnsignedTx era + -> ShelleyWitnessSigningKey + -> L.WitVKey L.Witness L.StandardCrypto +makeKeyWitness era (UnsignedTx unsignedTx) wsk = + obtainCommonConstraints era $ + let txbody = unsignedTx ^. L.bodyTxL + txhash :: L.Hash L.StandardCrypto EraIndependentTxBody + txhash = obtainCommonConstraints era $ hashTxBody txbody + sk = toShelleySigningKey wsk + vk = getShelleyKeyWitnessVerificationKey sk + signature = makeShelleySignature txhash sk + in L.WitVKey vk signature + +signTx + :: Era era + -> [L.BootstrapWitness L.StandardCrypto] + -> [L.WitVKey L.Witness L.StandardCrypto] + -> UnsignedTx era + -> Ledger.Tx (LedgerEra era) +signTx era bootstrapWits shelleyKeyWits (UnsignedTx unsigned) = + obtainCommonConstraints era $ + let currentScriptWitnesses = unsigned ^. L.witsTxL + keyWits = + obtainCommonConstraints era $ + L.mkBasicTxWits + & L.addrTxWitsL + .~ Set.fromList shelleyKeyWits + & L.bootAddrTxWitsL + .~ Set.fromList bootstrapWits + signedTx = unsigned & L.witsTxL .~ (keyWits <> currentScriptWitnesses) + in signedTx + +-- Compatibility related. Will be removed once the old api has been deprecated and deleted. + +convertTxBodyToUnsignedTx + :: ShelleyBasedEra era -> TxBody era -> UnsignedTx (ApiEraToExperimentalEra era) +convertTxBodyToUnsignedTx sbe txbody = + caseShelleyToAlonzoOrBabbageEraOnwards + (const $ error "convertTxBodyToUnsignedTx: Error") + ( \w -> + let ShelleyTx _ unsignedLedgerTx = makeSignedTransaction [] txbody + in UnsignedTx $ obtainShimConstraints w unsignedLedgerTx + ) + sbe diff --git a/cardano-api/internal/Cardano/Api/Fees.hs b/cardano-api/internal/Cardano/Api/Fees.hs index 477ab4611..ba1a9dbdb 100644 --- a/cardano-api/internal/Cardano/Api/Fees.hs +++ b/cardano-api/internal/Cardano/Api/Fees.hs @@ -8,6 +8,7 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE UndecidableInstances #-} -- | Fee calculation module Cardano.Api.Fees @@ -18,6 +19,7 @@ module Cardano.Api.Fees -- * Script execution units , evaluateTransactionExecutionUnits + , evaluateTransactionExecutionUnitsShelley , ScriptExecutionError (..) , TransactionValidityError (..) @@ -52,9 +54,13 @@ import Cardano.Api.Eon.BabbageEraOnwards import Cardano.Api.Eon.ConwayEraOnwards import Cardano.Api.Eon.MaryEraOnwards import Cardano.Api.Eon.ShelleyBasedEra +import Cardano.Api.Eon.ShelleyToAlonzoEra import Cardano.Api.Eras.Case import Cardano.Api.Eras.Core import Cardano.Api.Error +import Cardano.Api.Experimental.Eras (obtainShimConstraints, sbeToEra) +import qualified Cardano.Api.Experimental.Eras as Exp +import Cardano.Api.Experimental.Tx import Cardano.Api.Feature import qualified Cardano.Api.Ledger.Lens as A import Cardano.Api.Pretty @@ -374,7 +380,7 @@ estimateBalancedTxBody return ( BalancedTxBody finalTxBodyContent - txbody3 + (convertTxBodyToUnsignedTx sbe txbody3) (TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone) fee ) @@ -799,24 +805,26 @@ evaluateTransactionBalance sbe pp poolids stakeDelegDeposits drepDelegDeposits u TxOutValueShelleyBased sbe $ L.evalBalanceTxBody pp - lookupDelegDeposit - lookupDRepDeposit - isRegPool + (lookupDelegDeposit stakeDelegDeposits) + (lookupDRepDeposit drepDelegDeposits) + (isRegPool poolids) (toLedgerUTxO sbe utxo) txbody - where - isRegPool :: Ledger.KeyHash Ledger.StakePool Ledger.StandardCrypto -> Bool - isRegPool kh = StakePoolKeyHash kh `Set.member` poolids - lookupDelegDeposit - :: Ledger.Credential 'Ledger.Staking L.StandardCrypto -> Maybe L.Coin - lookupDelegDeposit stakeCred = - Map.lookup (fromShelleyStakeCredential stakeCred) stakeDelegDeposits +isRegPool :: Set PoolId -> Ledger.KeyHash Ledger.StakePool Ledger.StandardCrypto -> Bool +isRegPool poolids kh = StakePoolKeyHash kh `Set.member` poolids + +lookupDelegDeposit + :: Map StakeCredential L.Coin -> Ledger.Credential 'Ledger.Staking L.StandardCrypto -> Maybe L.Coin +lookupDelegDeposit stakeDelegDeposits stakeCred = + Map.lookup (fromShelleyStakeCredential stakeCred) stakeDelegDeposits - lookupDRepDeposit - :: Ledger.Credential 'Ledger.DRepRole L.StandardCrypto -> Maybe L.Coin - lookupDRepDeposit drepCred = - Map.lookup drepCred drepDelegDeposits +lookupDRepDeposit + :: Map (Ledger.Credential Ledger.DRepRole Ledger.StandardCrypto) L.Coin + -> Ledger.Credential 'Ledger.DRepRole L.StandardCrypto + -> Maybe L.Coin +lookupDRepDeposit drepDelegDeposits drepCred = + Map.lookup drepCred drepDelegDeposits -- ---------------------------------------------------------------------------- -- Automated transaction building @@ -863,6 +871,7 @@ data TxBodyErrorAutoBalance era | TxBodyErrorScriptWitnessIndexMissingFromExecUnitsMap ScriptWitnessIndex (Map ScriptWitnessIndex ExecutionUnits) + | TxBodyErrorDeprecatedEra (Exp.DeprecatedEra era) deriving Show instance Error (TxBodyErrorAutoBalance era) where @@ -916,6 +925,8 @@ instance Error (TxBodyErrorAutoBalance era) where [ "ScriptWitnessIndex (redeemer pointer): " <> pshow sIndex <> " is missing from the execution " , "units (redeemer pointer) map: " <> pshow eUnitsMap ] + TxBodyErrorDeprecatedEra deprecatedEra -> + "The era " <> pretty deprecatedEra <> " is deprecated and no longer supported." handleExUnitsErrors :: ScriptValidity @@ -934,15 +945,18 @@ handleExUnitsErrors ScriptInvalid failuresMap exUnitsMap | null failuresMap = Left TxBodyScriptBadScriptValidity | otherwise = Right $ Map.map (\_ -> ExecutionUnits 0 0) failuresMap <> exUnitsMap -data BalancedTxBody era - = BalancedTxBody - (TxBodyContent BuildTx era) - (TxBody era) - (TxOut CtxTx era) - -- ^ Transaction balance (change output) - L.Coin - -- ^ Estimated transaction fee - deriving Show +data BalancedTxBody era where + BalancedTxBody + :: (TxBodyContent BuildTx era) + -> (UnsignedTx (Exp.ApiEraToExperimentalEra era)) + -> (TxOut CtxTx era) + -- ^ Transaction balance (change output) + -> L.Coin + -- ^ Estimated transaction fee + -> BalancedTxBody era + +deriving instance + (Exp.IsEra (Exp.ApiEraToExperimentalEra era), IsShelleyBasedEra era) => Show (BalancedTxBody era) newtype RequiredShelleyKeyWitnesses = RequiredShelleyKeyWitnesses {unRequiredShelleyKeyWitnesses :: Int} @@ -1037,167 +1051,186 @@ makeTransactionBodyAutoBalance txbodycontent changeaddr mnkeys = - shelleyBasedEraConstraints sbe $ do - -- Our strategy is to: - -- 1. evaluate all the scripts to get the exec units, update with ex units - -- 2. figure out the overall min fees - -- 3. update tx with fees - -- 4. balance the transaction and update tx change output - txbody0 <- - first TxBodyError $ - createAndValidateTransactionBody - sbe - txbodycontent - { txOuts = - txOuts txbodycontent - ++ [TxOut changeaddr (lovelaceToTxOutValue sbe 0) TxOutDatumNone ReferenceScriptNone] - -- TODO: think about the size of the change output - -- 1,2,4 or 8 bytes? - } - - exUnitsMapWithLogs <- - first TxBodyErrorValidityInterval $ - evaluateTransactionExecutionUnits - era - systemstart - history - lpp - utxo - txbody0 - let exUnitsMap = Map.map (fmap snd) exUnitsMapWithLogs - - exUnitsMap' <- - case Map.mapEither id exUnitsMap of - (failures, exUnitsMap') -> - handleExUnitsErrors - (txScriptValidityToScriptValidity (txScriptValidity txbodycontent)) - failures - exUnitsMap' - - txbodycontent1 <- substituteExecutionUnits exUnitsMap' txbodycontent - - -- Make a txbody that we will use for calculating the fees. For the purpose - -- of fees we just need to make a txbody of the right size in bytes. We do - -- not need the right values for the fee or change output. We use - -- "big enough" values for the change output and set so that the CBOR - -- encoding size of the tx will be big enough to cover the size of the final - -- output and fee. Yes this means this current code will only work for - -- final fee of less than around 4000 ada (2^32-1 lovelace) and change output - -- of less than around 18 trillion ada (2^64-1 lovelace). - -- However, since at this point we know how much non-Ada change to give - -- we can use the true values for that. - let maxLovelaceChange = L.Coin (2 ^ (64 :: Integer)) - 1 - let maxLovelaceFee = L.Coin (2 ^ (32 :: Integer) - 1) - - let totalValueAtSpendableUTxO = fromLedgerValue sbe $ calculateIncomingUTxOValue $ Map.elems $ unUTxO utxo - let change = - forShelleyBasedEraInEon - sbe - mempty - (\w -> toLedgerValue w $ calculateChangeValue sbe totalValueAtSpendableUTxO txbodycontent1) - let changeWithMaxLovelace = change & A.adaAssetL sbe .~ maxLovelaceChange - let changeTxOut = - forShelleyBasedEraInEon - sbe - (lovelaceToTxOutValue sbe maxLovelaceChange) - (\w -> maryEraOnwardsConstraints w $ TxOutValueShelleyBased sbe changeWithMaxLovelace) - - let (dummyCollRet, dummyTotColl) = maybeDummyTotalCollAndCollReturnOutput sbe txbodycontent changeaddr - txbody1 <- - first TxBodyError $ -- TODO: impossible to fail now - createAndValidateTransactionBody - sbe - txbodycontent1 - { txFee = TxFeeExplicit sbe maxLovelaceFee - , txOuts = - TxOut changeaddr changeTxOut TxOutDatumNone ReferenceScriptNone - : txOuts txbodycontent - , txReturnCollateral = dummyCollRet - , txTotalCollateral = dummyTotColl - } - -- NB: This has the potential to over estimate the fees because estimateTransactionKeyWitnessCount - -- makes the conservative assumption that all inputs are from distinct - -- addresses. - let nkeys = - fromMaybe - (estimateTransactionKeyWitnessCount txbodycontent1) - mnkeys - fee = calculateMinTxFee sbe pp utxo txbody1 nkeys - (retColl, reqCol) = - caseShelleyToAlonzoOrBabbageEraOnwards - (const (TxReturnCollateralNone, TxTotalCollateralNone)) - ( \w -> - let collIns = case txInsCollateral txbodycontent of - TxInsCollateral _ collIns' -> collIns' - TxInsCollateralNone -> mempty - collateralOuts = catMaybes [Map.lookup txin (unUTxO utxo) | txin <- collIns] - totalPotentialCollateral = mconcat $ map (\(TxOut _ txOutVal _ _) -> txOutValueToLovelace txOutVal) collateralOuts - in calcReturnAndTotalCollateral - w - fee + caseShelleyToAlonzoOrBabbageEraOnwards + (Left . TxBodyErrorDeprecatedEra . Exp.DeprecatedEra . shelleyToAlonzoEraToShelleyBasedEra) + ( \bEraOnwards -> + shelleyBasedEraConstraints sbe $ do + availableEra <- first TxBodyErrorDeprecatedEra $ sbeToEra sbe + + -- Our strategy is to: + -- 1. evaluate all the scripts to get the exec units, update with ex units + -- 2. figure out the overall min fees + -- 3. update tx with fees + -- 4. balance the transaction and update tx change output + UnsignedTx unsignedTx0 <- + first TxBodyError + $ makeUnsignedTx + availableEra + $ obtainShimConstraints bEraOnwards + $ txbodycontent + { txOuts = + txOuts txbodycontent + ++ [TxOut changeaddr (lovelaceToTxOutValue sbe 0) TxOutDatumNone ReferenceScriptNone] + -- TODO: think about the size of the change output + -- 1,2,4 or 8 bytes? + } + exUnitsMapWithLogs <- + first TxBodyErrorValidityInterval + $ evaluateTransactionExecutionUnitsShelley + sbe + systemstart + history + lpp + utxo + $ obtainShimConstraints bEraOnwards unsignedTx0 + + let exUnitsMap = Map.map (fmap snd) exUnitsMapWithLogs + + exUnitsMap' <- + case Map.mapEither id exUnitsMap of + (failures, exUnitsMap') -> + handleExUnitsErrors + (txScriptValidityToScriptValidity (txScriptValidity txbodycontent)) + failures + exUnitsMap' + + txbodycontent1 <- substituteExecutionUnits exUnitsMap' txbodycontent + + -- Make a txbody that we will use for calculating the fees. For the purpose + -- of fees we just need to make a txbody of the right size in bytes. We do + -- not need the right values for the fee or change output. We use + -- "big enough" values for the change output and set so that the CBOR + -- encoding size of the tx will be big enough to cover the size of the final + -- output and fee. Yes this means this current code will only work for + -- final fee of less than around 4000 ada (2^32-1 lovelace) and change output + -- of less than around 18 trillion ada (2^64-1 lovelace). + -- However, since at this point we know how much non-Ada change to give + -- we can use the true values for that. + let maxLovelaceChange = L.Coin (2 ^ (64 :: Integer)) - 1 + let maxLovelaceFee = L.Coin (2 ^ (32 :: Integer) - 1) + + let totalValueAtSpendableUTxO = fromLedgerValue sbe $ calculateIncomingUTxOValue $ Map.elems $ unUTxO utxo + let change = + forShelleyBasedEraInEon + sbe + mempty + (\w -> toLedgerValue w $ calculateChangeValue sbe totalValueAtSpendableUTxO txbodycontent1) + let changeWithMaxLovelace = change & A.adaAssetL sbe .~ maxLovelaceChange + let changeTxOut = + forShelleyBasedEraInEon + sbe + (lovelaceToTxOutValue sbe maxLovelaceChange) + (\w -> maryEraOnwardsConstraints w $ TxOutValueShelleyBased sbe changeWithMaxLovelace) + + let (dummyCollRet, dummyTotColl) = maybeDummyTotalCollAndCollReturnOutput sbe txbodycontent changeaddr + UnsignedTx txbody1 <- + first TxBodyError + $ makeUnsignedTx -- TODO: impossible to fail now + availableEra + $ obtainShimConstraints bEraOnwards + $ txbodycontent1 + { txFee = TxFeeExplicit sbe maxLovelaceFee + , txOuts = + TxOut changeaddr changeTxOut TxOutDatumNone ReferenceScriptNone + : txOuts txbodycontent + , txReturnCollateral = dummyCollRet + , txTotalCollateral = dummyTotColl + } + -- NB: This has the potential to over estimate the fees because estimateTransactionKeyWitnessCount + -- makes the conservative assumption that all inputs are from distinct + -- addresses. + let nkeys = + fromMaybe + (estimateTransactionKeyWitnessCount txbodycontent1) + mnkeys + fee = + obtainShimConstraints bEraOnwards $ + L.calcMinFeeTx (toLedgerUTxO sbe utxo) pp txbody1 (fromIntegral nkeys) + (retColl, reqCol) = + caseShelleyToAlonzoOrBabbageEraOnwards + (const (TxReturnCollateralNone, TxTotalCollateralNone)) + ( \w -> + let collIns = case txInsCollateral txbodycontent of + TxInsCollateral _ collIns' -> collIns' + TxInsCollateralNone -> mempty + collateralOuts = catMaybes [Map.lookup txin (unUTxO utxo) | txin <- collIns] + totalPotentialCollateral = mconcat $ map (\(TxOut _ txOutVal _ _) -> txOutValueToLovelace txOutVal) collateralOuts + in calcReturnAndTotalCollateral + w + fee + pp + (txInsCollateral txbodycontent) + (txReturnCollateral txbodycontent) + (txTotalCollateral txbodycontent) + changeaddr + totalPotentialCollateral + ) + sbe + + -- Make a txbody for calculating the balance. For this the size of the tx + -- does not matter, instead it's just the values of the fee and outputs. + -- Here we do not want to start with any change output, since that's what + -- we need to calculate. + UnsignedTx txbody2 <- + first TxBodyError + $ makeUnsignedTx -- TODO: impossible to fail now + availableEra + $ obtainShimConstraints bEraOnwards + $ txbodycontent1 + { txFee = TxFeeExplicit sbe fee + , txReturnCollateral = retColl + , txTotalCollateral = reqCol + } + let balance = + TxOutValueShelleyBased sbe $ + obtainShimConstraints bEraOnwards $ + L.evalBalanceTxBody pp - (txInsCollateral txbodycontent) - (txReturnCollateral txbodycontent) - (txTotalCollateral txbodycontent) - changeaddr - totalPotentialCollateral + (lookupDelegDeposit stakeDelegDeposits) + (lookupDRepDeposit drepDelegDeposits) + (isRegPool poolids) + (toLedgerUTxO sbe utxo) + (txbody2 ^. L.bodyTxL) + + forM_ (txOuts txbodycontent1) $ \txout -> checkMinUTxOValue sbe txout pp + + -- check if the balance is positive or negative + -- in one case we can produce change, in the other the inputs are insufficient + balanceCheck sbe pp changeaddr balance + + -- TODO: we could add the extra fee for the CBOR encoding of the change, + -- now that we know the magnitude of the change: i.e. 1-8 bytes extra. + + -- The txbody with the final fee and change output. This should work + -- provided that the fee and change are less than 2^32-1, and so will + -- fit within the encoding size we picked above when calculating the fee. + -- Yes this could be an over-estimate by a few bytes if the fee or change + -- would fit within 2^16-1. That's a possible optimisation. + let finalTxBodyContent = + txbodycontent1 + { txFee = TxFeeExplicit sbe fee + , txOuts = + accountForNoChange + (TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone) + (txOuts txbodycontent) + , txReturnCollateral = retColl + , txTotalCollateral = reqCol + } + txbody3 <- + first TxBodyError $ -- TODO: impossible to fail now. We need to implement a function + -- that simply creates a transaction body because we have already + -- validated the transaction body earlier within makeTransactionBodyAutoBalance + makeUnsignedTx availableEra $ + obtainShimConstraints bEraOnwards finalTxBodyContent + return + ( BalancedTxBody + finalTxBodyContent + txbody3 + (TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone) + fee ) - sbe - - -- Make a txbody for calculating the balance. For this the size of the tx - -- does not matter, instead it's just the values of the fee and outputs. - -- Here we do not want to start with any change output, since that's what - -- we need to calculate. - txbody2 <- - first TxBodyError $ -- TODO: impossible to fail now - createAndValidateTransactionBody - sbe - txbodycontent1 - { txFee = TxFeeExplicit sbe fee - , txReturnCollateral = retColl - , txTotalCollateral = reqCol - } - let balance = evaluateTransactionBalance sbe pp poolids stakeDelegDeposits drepDelegDeposits utxo txbody2 - - forM_ (txOuts txbodycontent1) $ \txout -> checkMinUTxOValue sbe txout pp - - -- check if the balance is positive or negative - -- in one case we can produce change, in the other the inputs are insufficient - balanceCheck sbe pp changeaddr balance - - -- TODO: we could add the extra fee for the CBOR encoding of the change, - -- now that we know the magnitude of the change: i.e. 1-8 bytes extra. - - -- The txbody with the final fee and change output. This should work - -- provided that the fee and change are less than 2^32-1, and so will - -- fit within the encoding size we picked above when calculating the fee. - -- Yes this could be an over-estimate by a few bytes if the fee or change - -- would fit within 2^16-1. That's a possible optimisation. - let finalTxBodyContent = - txbodycontent1 - { txFee = TxFeeExplicit sbe fee - , txOuts = - accountForNoChange - (TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone) - (txOuts txbodycontent) - , txReturnCollateral = retColl - , txTotalCollateral = reqCol - } - txbody3 <- - first TxBodyError $ -- TODO: impossible to fail now. We need to implement a function - -- that simply creates a transaction body because we have already - -- validated the transaction body earlier within makeTransactionBodyAutoBalance - createAndValidateTransactionBody sbe finalTxBodyContent - return - ( BalancedTxBody - finalTxBodyContent - txbody3 - (TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone) - fee - ) - where - era :: CardanoEra era - era = toCardanoEra sbe + ) + sbe -- | In the event of spending the exact amount of lovelace in -- the specified input(s), this function excludes the change diff --git a/cardano-api/internal/Cardano/Api/Protocol/Version.hs b/cardano-api/internal/Cardano/Api/Protocol/Version.hs deleted file mode 100644 index 21af782d9..000000000 --- a/cardano-api/internal/Cardano/Api/Protocol/Version.hs +++ /dev/null @@ -1,155 +0,0 @@ -{-# LANGUAGE ConstraintKinds #-} -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE PatternSynonyms #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeFamilyDependencies #-} --- UndecidableInstances needed for 9.2.7 and 8.10.7 -{-# LANGUAGE UndecidableInstances #-} --- Only for UninhabitableType -{-# OPTIONS_GHC -fno-warn-unused-top-binds #-} - --- | This module defines the protocol versions corresponding to the eras in the Cardano blockchain. -module Cardano.Api.Protocol.Version - ( BabbageEra - , ConwayEra - , pattern CurrentEra - , pattern UpcomingEra - , Era (..) - , UseEra - , VersionToSbe - , useEra - , protocolVersionToSbe - ) -where - -import Cardano.Api.Eon.ShelleyBasedEra (ShelleyBasedEra (..)) -import qualified Cardano.Api.Eras.Core as Api - -import GHC.TypeLits - --- | Users typically interact with the latest features on the mainnet or experiment with features --- from the upcoming era. Hence, the protocol versions are limited to the current mainnet era --- and the next era (upcoming era). -data BabbageEra - -data ConwayEra - --- Allows us to gradually change the api without breaking things. --- This will eventually be removed. -type family VersionToSbe version where - VersionToSbe BabbageEra = Api.BabbageEra - VersionToSbe ConwayEra = Api.ConwayEra - --- | Represents the eras in Cardano's blockchain. --- --- Instead of enumerating every possible era, we use two constructors: --- 'CurrentEra' and 'UpcomingEra'. This design simplifies the handling --- of eras, especially for 'cardano-api' consumers who are primarily concerned --- with the current mainnet era and the next era for an upcoming hardfork. --- --- Usage: --- - 'CurrentEra': Reflects the era currently active on mainnet. --- - 'UpcomingEra': Represents the era planned for the next hardfork. --- --- After a hardfork, 'cardano-api' should be updated promptly to reflect --- the new mainnet era in 'CurrentEra'. -data Era version where - -- | The era currently active on Cardano's mainnet. - CurrentEraInternal :: Era BabbageEra - -- | The era planned for the next hardfork on Cardano's mainnet. - UpcomingEraInternal :: Era ConwayEra - --- | How to deprecate an era --- --- 1. Add DEPRECATED pragma to the era type tag. --- @ --- {-# DEPRECATED BabbageEra "BabbageEra no longer supported, use ConwayEra" #-} --- data BabbageEra --- @ --- --- 2. Add a new era type tag. --- @ --- data Era version where --- -- | The era currently active on Cardano's mainnet. --- CurrentEraInternal :: Era ConwayEra --- -- | The era planned for the next hardfork on Cardano's mainnet. --- UpcomingEraInternal :: Era (UninhabitableType EraCurrentlyNonExistent) --- @ --- --- 3. Update pattern synonyms. --- @ --- pattern CurrentEra :: Era ConwayEra --- pattern CurrentEra = CurrentEraInternal --- --- pattern UpcomingEra :: Era (UninhabitableType EraCurrentlyNonExistent) --- pattern UpcomingEra = UpcomingEraInternal --- @ --- --- 4. Add new 'UseEra' instance and keep the deprecated era's instance. --- @ --- instance UseEra BabbageEra where --- useEra = error "useEra: BabbageEra no longer supported, use ConwayEra" --- --- instance UseEra ConwayEra where --- useEra = CurrentEra --- @ --- --- 5. Update 'protocolVersionToSbe' as follows: --- @ --- protocolVersionToSbe --- :: Era version --- -> Maybe (ShelleyBasedEra (VersionToSbe version)) --- protocolVersionToSbe CurrentEraInternal = Just ShelleyBasedEraBabbage --- protocolVersionToSbe UpcomingEraInternal = Nothing --- @ - --- | 'CurrentEraInternal' and 'UpcomingEraInternal' are for internal use only. --- The above restriction combined with the following pattern synonyms --- prevents a user from pattern matching on 'Era era' and --- avoids the following situation: --- --- @ --- doThing :: Era era -> () --- doThing = \case --- CurrentEraInternal -> enableFeature --- UpcomingEraInternal -> disableFeature --- @ --- --- Consumers of this library must pick one of the two eras while --- this library is responsibile for what happens at the boundary of the eras. -pattern CurrentEra :: Era BabbageEra -pattern CurrentEra = CurrentEraInternal - -pattern UpcomingEra :: Era ConwayEra -pattern UpcomingEra = UpcomingEraInternal - -{-# COMPLETE CurrentEra, UpcomingEra #-} - -protocolVersionToSbe - :: Era version - -> Maybe (ShelleyBasedEra (VersionToSbe version)) -protocolVersionToSbe CurrentEraInternal = Just ShelleyBasedEraBabbage -protocolVersionToSbe UpcomingEraInternal = Nothing - -------------------------------------------------------------------------- - --- | Type class interface for the 'Era' type. -class UseEra version where - useEra :: Era version - -instance UseEra BabbageEra where - useEra = CurrentEra - -instance UseEra ConwayEra where - useEra = UpcomingEra - --- | After a hardfork there is usually no planned upcoming era --- that we are able to experiment with. We force a type era --- in this instance. See docs above. -data EraCurrentlyNonExistent - -type family UninhabitableType a where - UninhabitableType EraCurrentlyNonExistent = - TypeError ('Text "There is currently no planned upcoming era. Use CurrentEra instead.") diff --git a/cardano-api/internal/Cardano/Api/Tx/Body.hs b/cardano-api/internal/Cardano/Api/Tx/Body.hs index a872aa8fe..3663882ed 100644 --- a/cardano-api/internal/Cardano/Api/Tx/Body.hs +++ b/cardano-api/internal/Cardano/Api/Tx/Body.hs @@ -134,6 +134,27 @@ module Cardano.Api.Tx.Body , scriptDataToInlineDatum -- * Internal conversion functions & types + , convCertificates + , convCollateralTxIns + , convExtraKeyWitnesses + , convLanguages + , convMintValue + , convReferenceInputs + , convReturnCollateral + , convScripts + , convScriptData + , convTotalCollateral + , convTransactionFee + , convTxIns + , convTxOuts + , convTxUpdateProposal + , convValidityLowerBound + , convValidityUpperBound + , convVotingProcedures + , convWithdrawals + , getScriptIntegrityHash + , mkCommonTxBody + , toAuxiliaryData , toByronTxId , toShelleyTxId , toShelleyTxIn diff --git a/cardano-api/src/Cardano/Api/Experimental.hs b/cardano-api/src/Cardano/Api/Experimental.hs index 9a7d4d398..3a4716fe5 100644 --- a/cardano-api/src/Cardano/Api/Experimental.hs +++ b/cardano-api/src/Cardano/Api/Experimental.hs @@ -1,17 +1,36 @@ -{-# LANGUAGE PatternSynonyms #-} - +-- | This module provides an experimental library interface that is intended +-- to replace the existing api. It is subject to dramatic changes so use with caution. module Cardano.Api.Experimental - ( -- * New Era interface - BabbageEra + ( -- * Tx related + UnsignedTx (..) + , UnsignedTxError (..) + , makeUnsignedTx + , makeKeyWitness + , signTx + , convertTxBodyToUnsignedTx + , EraCommonConstraints + , EraShimConstraints + , obtainShimConstraints + , obtainCommonConstraints + , hashTxBody + , evaluateTransactionExecutionUnitsShelley + -- Era related + , BabbageEra , ConwayEra - , Era - , pattern CurrentEra - , pattern UpcomingEra - , UseEra - , VersionToSbe + , Era (..) + , LedgerEra + , IsEra + , ApiEraToLedgerEra + , ExperimentalEraToApiEra + , ApiEraToExperimentalEra + , DeprecatedEra (..) , useEra - , protocolVersionToSbe + , eraToSbe + , babbageEraOnwardsToEra + , sbeToEra ) where -import Cardano.Api.Protocol.Version +import Cardano.Api.Experimental.Eras +import Cardano.Api.Experimental.Tx +import Cardano.Api.Fees (evaluateTransactionExecutionUnitsShelley) diff --git a/cardano-api/src/Cardano/Api/Shelley.hs b/cardano-api/src/Cardano/Api/Shelley.hs index 5d0cefa25..6ae36572f 100644 --- a/cardano-api/src/Cardano/Api/Shelley.hs +++ b/cardano-api/src/Cardano/Api/Shelley.hs @@ -269,6 +269,7 @@ module Cardano.Api.Shelley -- ** Various calculations , LeadershipError (..) , currentEpochEligibleLeadershipSlots + , evaluateTransactionExecutionUnitsShelley , nextEpochEligibleLeadershipSlots -- ** Conversions @@ -293,6 +294,7 @@ import Cardano.Api.Block import Cardano.Api.Certificate import Cardano.Api.DRepMetadata import Cardano.Api.Eon.ShelleyBasedEra +import Cardano.Api.Fees import Cardano.Api.Genesis import Cardano.Api.Governance.Actions.ProposalProcedure import Cardano.Api.Governance.Actions.VotingProcedure diff --git a/hls.log b/hls.log new file mode 100644 index 000000000..82f9ee2b9 --- /dev/null +++ b/hls.log @@ -0,0 +1,52839 @@ +2024-06-20T09:19:06.396591Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-20T09:19:06.397577Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-20T09:19:06.397845Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-20T09:19:06.400784Z | Info | Logging heap statistics every 60.00s +2024-06-20T09:19:06.410496Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-20T09:19:06.410973Z | Info | Starting server +2024-06-20T09:20:06.458063Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:21:06.518091Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:22:06.578930Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:23:06.639559Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:24:06.698071Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:25:06.757924Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:26:06.818017Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:27:06.877998Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:28:06.937856Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:29:06.982342Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:30:07.042954Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:31:07.101908Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:32:07.142112Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:33:07.202643Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:34:07.263446Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:35:07.322009Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:36:07.381892Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:37:07.442034Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:38:07.502049Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:39:07.562129Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:40:07.622098Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:41:07.681900Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:42:07.742048Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:43:07.801945Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:44:07.861920Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:45:07.921997Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:46:07.981956Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:47:07.985872Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:48:08.046068Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:49:08.105873Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:50:08.165942Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:51:08.226620Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:52:08.285949Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:53:08.345992Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:54:08.406035Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:55:08.436909Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:56:08.497342Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:57:08.558004Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:58:08.618600Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T09:59:08.677991Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:00:08.738648Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:01:08.799306Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:02:08.859990Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:03:08.918009Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:04:08.978605Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:05:09.037890Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:06:09.097944Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:07:09.158544Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:08:09.217909Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:09:09.278518Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:10:09.337935Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:11:09.398076Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:12:09.457985Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:13:09.518017Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:14:09.527533Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:15:09.585736Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:16:09.645924Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:17:09.705817Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:18:09.766111Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:19:09.826828Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:20:09.874664Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:21:09.933936Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T10:22:09.993931Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:27:47.283760Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:28:47.343799Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:29:47.401525Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:30:47.459499Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:31:47.519592Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:32:47.579538Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:33:47.640104Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:34:47.700527Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:35:47.759503Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:36:47.819542Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:37:47.823549Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:38:47.884021Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:39:47.944532Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:40:48.003422Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:41:48.035555Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:42:48.095692Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:43:48.155628Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:44:48.199614Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20 11:47:00.4710000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-20 11:47:00.4800000 [client] INFO Finding haskell-language-server +2024-06-20 11:47:00.4820000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:00.4830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:00.5060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-20 11:47:00.9210000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:00.9210000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:00.9300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-20 11:47:01.1650000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:01.1650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:01.1720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-20 11:47:01.5060000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:01.5060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:01.5230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-20 11:47:01.8130000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:01.8130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:01.8260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-20 11:47:01.8550000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:01.8560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:01.8690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-20 11:47:01.8860000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:01.8860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:01.8940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-20 11:47:01.9270000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-20 11:47:02.0040000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:02.0040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:02.0140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-20 11:47:02.2700000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-20 11:47:02.2720000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-20 11:47:19.8170000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-20 11:47:20.0160000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-20 11:47:20.0160000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:20.0180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:20.0420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-20 11:47:20.7430000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:20.7450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:20.7740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-20 11:47:20.8680000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:20.8690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:20.8990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-20 11:47:20.9600000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:20.9600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:20.9890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-20 11:47:21.0260000 [client] INFO Checking for ghcup installation +2024-06-20 11:47:21.0270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 11:47:21.0560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-20 11:47:21.6410000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-20 11:47:21.6470000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-20 11:47:21.6470000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-20 11:47:21.6470000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-20 11:47:21.6470000 [client] INFO server environment variables: +2024-06-20 11:47:21.6470000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-20 11:47:21.6470000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-20 11:47:21.6470000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-20 11:47:21.6520000 [client] INFO Starting language server +2024-06-20T11:48:11.635275Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-20T11:48:11.637907Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-20T11:48:11.638492Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-20T11:48:11.645539Z | Info | Logging heap statistics every 60.00s +2024-06-20T11:48:11.664186Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-20T11:48:11.664722Z | Info | Starting server +2024-06-20T11:48:11.683907Z | Info | Started LSP server in 0.02s +2024-06-20T11:48:17.199870Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-20T11:48:17.832212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-20T11:49:11.700531Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:50:11.758503Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:51:11.820607Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:52:11.879870Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:53:11.938500Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:54:11.998496Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:55:12.058622Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:56:12.118458Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:57:12.178581Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:58:12.238519Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T11:59:12.291829Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:00:12.312861Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:01:12.363601Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:02:12.422543Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:03:12.482672Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:04:12.543234Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:05:12.552134Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:06:12.612642Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:07:12.670642Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:08:12.730729Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:09:12.790538Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:10:12.850489Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:11:12.910635Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:12:12.971315Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:13:13.032014Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:14:13.090545Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:15:13.151396Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:16:13.210608Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:17:13.222571Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:18:13.283293Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:19:13.290625Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:20:13.350539Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:20:32.395057Z | Info | Cradle path: cardano-api/internal/Cardano/Api/LedgerState.hs +2024-06-20T12:20:32.396210Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-20T12:20:32.482514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-20T12:20:34.892575Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT6898-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-20T12:20:36.804153Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.0-inplace-internal-dbba1c3b1a6cfec6796e6794ed16f4a691889bdf +2024-06-20T12:20:36.809060Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.0-inplace-internal] +2024-06-20T12:21:13.386628Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:22:13.446508Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:23:13.486531Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:24:13.490511Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:25:13.538532Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:26:13.598957Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:27:13.658542Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:28:13.718435Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:29:13.722530Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:30:13.782528Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:31:13.798582Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:32:13.858499Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:33:13.918867Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:34:13.978472Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:35:14.038480Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:36:14.098880Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:37:14.116457Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:38:14.176998Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:39:14.237502Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:40:14.298110Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:41:14.358201Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:42:14.418620Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:43:14.478417Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:44:14.536706Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:45:14.569967Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:46:14.630601Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:47:14.691205Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:48:14.751910Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:49:14.810615Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:50:14.870613Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:51:14.930712Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:52:14.991326Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:53:15.052046Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:54:15.062661Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:55:15.122724Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:56:15.135017Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:57:15.194647Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:58:15.255377Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T12:59:15.316087Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:00:15.363185Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:01:15.422521Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:02:15.482587Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:03:15.542635Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:04:15.602451Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:05:15.662548Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:06:15.722465Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-20T13:06:33.489467Z | Info | Reactor thread stopped +2024-06-20T13:06:33.492590Z | Error | Got EOF +2024-06-20 13:38:52.2950000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-20 13:38:52.2970000 [client] INFO Finding haskell-language-server +2024-06-20 13:38:52.2990000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:52.2990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:52.3080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-20 13:38:52.6780000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:52.6780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:52.6840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-20 13:38:52.9120000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:52.9120000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:52.9190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-20 13:38:53.1570000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:53.1570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:53.1620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-20 13:38:53.3630000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:53.3630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:53.3710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-20 13:38:53.3890000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:53.3900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:53.3950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-20 13:38:53.4220000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:53.4230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:53.4280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-20 13:38:53.4480000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-20 13:38:53.4950000 [client] INFO Checking for ghcup installation +2024-06-20 13:38:53.4950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:38:53.5020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-20 13:38:53.7000000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-20 13:38:53.7020000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-20 13:39:03.8120000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-20 13:39:03.8720000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-20 13:39:03.8730000 [client] INFO Checking for ghcup installation +2024-06-20 13:39:03.8730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:39:03.8790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-20 13:39:04.0050000 [client] INFO Checking for ghcup installation +2024-06-20 13:39:04.0060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:39:04.0130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-20 13:39:04.0330000 [client] INFO Checking for ghcup installation +2024-06-20 13:39:04.0330000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:39:04.0390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-20 13:39:04.0550000 [client] INFO Checking for ghcup installation +2024-06-20 13:39:04.0560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:39:04.0610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-20 13:39:04.0780000 [client] INFO Checking for ghcup installation +2024-06-20 13:39:04.0780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-20 13:39:04.0850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-20 13:39:04.2240000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-20 13:39:04.2250000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-20 13:39:04.2250000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-20 13:39:04.2250000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-20 13:39:04.2250000 [client] INFO server environment variables: +2024-06-20 13:39:04.2250000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-20 13:39:04.2250000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-20 13:39:04.2250000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-20 13:39:04.2270000 [client] INFO Starting language server +2024-06-20T13:39:18.990797Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-20T13:39:18.992052Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-20T13:39:18.992285Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-20T13:39:18.995060Z | Info | Logging heap statistics every 60.00s +2024-06-20T13:39:19.004879Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-20T13:39:19.005568Z | Info | Starting server +2024-06-20T13:39:19.008021Z | Info | Started LSP server in 0.00s +2024-06-20T13:39:20.957309Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-20T13:39:20.970746Z | Info | Cradle path: cardano-api/internal/Cardano/Api/LedgerState.hs +2024-06-20T13:39:20.972111Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-20T13:39:21.487963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-20T13:39:24.611115Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT220938-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-20T13:39:27.493669Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.0-inplace-internal-dbba1c3b1a6cfec6796e6794ed16f4a691889bdf +2024-06-20T13:39:27.505414Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.0-inplace-internal] +2024-06-20T13:40:18.996181Z | Info | Live bytes: 48.68MB Heap size: 1205.86MB +2024-06-20T13:41:18.997146Z | Info | Live bytes: 48.73MB Heap size: 1205.86MB +2024-06-20T13:42:18.998489Z | Info | Live bytes: 48.74MB Heap size: 1205.86MB +2024-06-20T13:42:43.966570Z | Info | Reactor thread stopped +2024-06-20T13:42:43.972248Z | Error | Got EOF +2024-06-23 10:32:04.5930000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-23 10:32:04.6030000 [client] INFO Finding haskell-language-server +2024-06-23 10:32:04.6040000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:04.6040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:04.6080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-23 10:32:04.8330000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:04.8330000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:04.8380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-23 10:32:04.9220000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:04.9220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:04.9260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-23 10:32:05.0130000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:05.0130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:05.0180000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-23 10:32:05.1070000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:05.1080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:05.1110000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-23 10:32:05.1250000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:05.1250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:05.1290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-23 10:32:05.1430000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:05.1430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:05.1490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-23 10:32:05.1700000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-23 10:32:05.2050000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:05.2060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:05.2100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-23 10:32:05.3040000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-23 10:32:05.3050000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-23 10:32:20.7200000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-23 10:32:20.8730000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-23 10:32:20.8740000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:20.8740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:20.8810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-23 10:32:20.9560000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:20.9560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:20.9610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-23 10:32:20.9780000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:20.9790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:20.9850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-23 10:32:21.0010000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:21.0010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:21.0070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-23 10:32:21.0210000 [client] INFO Checking for ghcup installation +2024-06-23 10:32:21.0210000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 10:32:21.0270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-23 10:32:21.1120000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-23 10:32:21.1120000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-23 10:32:21.1120000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-23 10:32:21.1120000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-23 10:32:21.1120000 [client] INFO server environment variables: +2024-06-23 10:32:21.1120000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-23 10:32:21.1120000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-23 10:32:21.1120000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-23 10:32:21.1130000 [client] INFO Starting language server +2024-06-23T10:32:30.336016Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-23T10:32:30.337837Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-23T10:32:30.338168Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-23T10:32:30.340695Z | Info | Logging heap statistics every 60.00s +2024-06-23T10:32:30.347030Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-23T10:32:30.347499Z | Info | Starting server +2024-06-23T10:32:30.360949Z | Info | Started LSP server in 0.01s +2024-06-23T10:32:31.689072Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-23T10:32:31.690349Z | Info | Reactor thread stopped +2024-06-23T10:32:31.695617Z | Error | Got EOF +2024-06-23 17:39:14.7790000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-23 17:39:14.7810000 [client] INFO Finding haskell-language-server +2024-06-23 17:39:14.7840000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:14.7840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:14.7930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-23 17:39:15.3280000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:15.3290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:15.3380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-23 17:39:15.6090000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:15.6100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:15.6200000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-23 17:39:15.9100000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:15.9110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:15.9170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-23 17:39:16.1390000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:16.1390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:16.1450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-23 17:39:16.1710000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:16.1710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:16.1790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-23 17:39:16.2040000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:16.2040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:16.2150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-23 17:39:16.2400000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-23 17:39:16.2950000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:16.2950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:16.3010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-23 17:39:16.5280000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-23 17:39:16.5290000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-23 17:39:27.0650000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-23 17:39:27.1200000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-23 17:39:27.1200000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:27.1200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:27.1250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-23 17:39:27.2110000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:27.2110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:27.2160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-23 17:39:27.2330000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:27.2330000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:27.2370000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-23 17:39:27.2510000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:27.2520000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:27.2560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-23 17:39:27.2700000 [client] INFO Checking for ghcup installation +2024-06-23 17:39:27.2700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-23 17:39:27.2750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-23 17:39:27.3590000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-23 17:39:27.3600000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-23 17:39:27.3600000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-23 17:39:27.3600000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-23 17:39:27.3600000 [client] INFO server environment variables: +2024-06-23 17:39:27.3600000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-23 17:39:27.3600000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-23 17:39:27.3600000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-23 17:39:27.3610000 [client] INFO Starting language server +2024-06-23T17:39:40.600960Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-23T17:39:40.602347Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-23T17:39:40.602765Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-23T17:39:40.607164Z | Info | Logging heap statistics every 60.00s +2024-06-23T17:39:40.621130Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-23T17:39:40.621833Z | Info | Starting server +2024-06-23T17:39:40.623888Z | Info | Started LSP server in 0.00s +2024-06-23T17:39:42.329219Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-23T17:39:42.340302Z | Info | Cradle path: cardano-api/internal/Cardano/Api/ScriptData.hs +2024-06-23T17:39:42.341329Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-23T17:39:42.920379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-23T17:39:45.924297Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT15007-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-23T17:39:52.030416Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-23T17:39:52.038335Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-23T17:40:40.608271Z | Info | Live bytes: 48.71MB Heap size: 1205.86MB +2024-06-23T17:41:17.570653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-23T17:41:29.875938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-23T17:41:29.879293Z | Info | Cradle path: cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/Address.hs +2024-06-23T17:41:29.879899Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-23T17:41:32.684753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-23T17:41:32.897501Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:test:cardano-api-test + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT15007-1 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-23T17:41:40.609720Z | Info | Live bytes: 61.10MB Heap size: 1224.74MB +2024-06-23T17:41:55.938320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-23T17:42:19.286151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-23T17:42:22.597123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-23T17:42:37.651936Z | Info | Reactor thread stopped +2024-06-23T17:42:37.667662Z | Error | Got EOF +2024-06-24 06:48:31.1300000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-24 06:48:31.1350000 [client] INFO Finding haskell-language-server +2024-06-24 06:48:31.1370000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:31.1370000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:31.1470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-24 06:48:31.4040000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:31.4040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:31.4120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-24 06:48:31.7080000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:31.7080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:31.7190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-24 06:48:31.9720000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:31.9720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:31.9800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-24 06:48:32.2450000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:32.2450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:32.2540000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-24 06:48:32.2800000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:32.2810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:32.2930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-24 06:48:32.3340000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:32.3350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:32.3530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-24 06:48:32.4200000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-24 06:48:32.4970000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:32.4970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:32.5090000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-24 06:48:32.7980000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-24 06:48:32.8020000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-24 06:48:43.3340000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-24 06:48:43.5960000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-24 06:48:43.5970000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:43.5970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:43.6030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-24 06:48:43.7110000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:43.7110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:43.7170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-24 06:48:43.7350000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:43.7350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:43.7400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-24 06:48:43.7550000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:43.7550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:43.7610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-24 06:48:43.7760000 [client] INFO Checking for ghcup installation +2024-06-24 06:48:43.7760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 06:48:43.7810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-24 06:48:43.8850000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-24 06:48:43.8860000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-24 06:48:43.8860000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-24 06:48:43.8860000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-24 06:48:43.8860000 [client] INFO server environment variables: +2024-06-24 06:48:43.8860000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-24 06:48:43.8860000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-24 06:48:43.8860000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-24 06:48:43.8880000 [client] INFO Starting language server +2024-06-24 07:59:28.2340000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-24 07:59:28.2350000 [client] INFO Finding haskell-language-server +2024-06-24 07:59:28.2360000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:28.2360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:28.2430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-24 07:59:28.5300000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:28.5300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:28.5380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-24 07:59:28.6690000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:28.6690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:28.6760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-24 07:59:28.7830000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:28.7840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:28.7900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-24 07:59:28.9590000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:28.9590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:28.9620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-24 07:59:28.9770000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:28.9770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:28.9850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-24 07:59:29.0060000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:29.0060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:29.0110000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-24 07:59:29.0380000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-24 07:59:29.0830000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:29.0840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:29.0890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-24 07:59:29.2240000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-24 07:59:29.2250000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-24 07:59:35.2610000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-24 07:59:35.3210000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-24 07:59:35.3210000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:35.3210000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:35.3290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-24 07:59:35.4050000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:35.4050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:35.4100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-24 07:59:35.4250000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:35.4260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:35.4290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-24 07:59:35.4430000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:35.4430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:35.4480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-24 07:59:35.4630000 [client] INFO Checking for ghcup installation +2024-06-24 07:59:35.4640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 07:59:35.4710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-24 07:59:35.5570000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-24 07:59:35.5570000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-24 07:59:35.5570000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-24 07:59:35.5570000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-24 07:59:35.5570000 [client] INFO server environment variables: +2024-06-24 07:59:35.5570000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-24 07:59:35.5570000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-24 07:59:35.5570000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-24 07:59:35.5580000 [client] INFO Starting language server +2024-06-24T07:59:44.535309Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-24T07:59:44.537436Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-24T07:59:44.537989Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-24T07:59:44.541742Z | Info | Logging heap statistics every 60.00s +2024-06-24T07:59:44.553090Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-24T07:59:44.553561Z | Info | Starting server +2024-06-24T07:59:44.566613Z | Info | Started LSP server in 0.01s +2024-06-24T07:59:45.722145Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-24T07:59:45.735439Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Address.hs +2024-06-24T07:59:45.736355Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-24T07:59:46.297350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-24T07:59:47.905940Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT62749-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-24T07:59:49.701790Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-24T07:59:49.706522Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-24T07:59:50.019637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-24T08:00:44.543531Z | Info | Live bytes: 64.59MB Heap size: 1233.13MB +2024-06-24T08:01:12.145620Z | Info | Reactor thread stopped +2024-06-24T08:01:12.158408Z | Error | Got EOF +2024-06-24 18:10:50.8660000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-24 18:10:50.8670000 [client] INFO Finding haskell-language-server +2024-06-24 18:10:50.8670000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:50.8670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:50.8730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-24 18:10:51.1460000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:51.1460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:51.1520000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-24 18:10:51.2780000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:51.2780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:51.2830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-24 18:10:51.3860000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:51.3860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:51.3920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-24 18:10:51.5140000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:51.5150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:51.5180000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-24 18:10:51.5320000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:51.5320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:51.5360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-24 18:10:51.5510000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:51.5510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:51.5580000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-24 18:10:51.5770000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-24 18:10:51.6100000 [client] INFO Checking for ghcup installation +2024-06-24 18:10:51.6110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:10:51.6150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-24 18:10:51.7230000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-24 18:10:51.7230000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-24 18:11:01.5190000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-24 18:11:01.5840000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-24 18:11:01.5840000 [client] INFO Checking for ghcup installation +2024-06-24 18:11:01.5840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:11:01.5910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-24 18:11:01.6660000 [client] INFO Checking for ghcup installation +2024-06-24 18:11:01.6660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:11:01.6700000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-24 18:11:01.6870000 [client] INFO Checking for ghcup installation +2024-06-24 18:11:01.6870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:11:01.6930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-24 18:11:01.7080000 [client] INFO Checking for ghcup installation +2024-06-24 18:11:01.7080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:11:01.7150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-24 18:11:01.7300000 [client] INFO Checking for ghcup installation +2024-06-24 18:11:01.7300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-24 18:11:01.7360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-24 18:11:01.8310000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-24 18:11:01.8320000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-24 18:11:01.8320000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-24 18:11:01.8320000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-24 18:11:01.8320000 [client] INFO server environment variables: +2024-06-24 18:11:01.8320000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-24 18:11:01.8320000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-24 18:11:01.8320000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-24 18:11:01.8330000 [client] INFO Starting language server +2024-06-24T18:11:10.613849Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-24T18:11:10.614832Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-24T18:11:10.615198Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-24T18:11:10.617958Z | Info | Logging heap statistics every 60.00s +2024-06-24T18:11:10.625102Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-24T18:11:10.625456Z | Info | Starting server +2024-06-24T18:11:10.626771Z | Info | Started LSP server in 0.00s +2024-06-24T18:11:11.759483Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-24T18:11:11.769844Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-06-24T18:11:11.770536Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-24T18:11:12.099571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-24T18:11:13.982379Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT534970-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-24T18:11:15.754461Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-24T18:11:15.759630Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-24T18:11:26.534623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-24T18:11:47.066599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-24T18:11:59.125685Z | Info | Reactor thread stopped +2024-06-24T18:11:59.137861Z | Error | Got EOF +2024-06-25 06:46:48.5010000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-25 06:46:48.5030000 [client] INFO Finding haskell-language-server +2024-06-25 06:46:48.5050000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:48.5050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:48.5140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-25 06:46:49.0390000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:49.0400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:49.0490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 06:46:49.2760000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:49.2760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:49.2830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-25 06:46:49.4900000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:49.4910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:49.5050000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-25 06:46:49.7180000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:49.7180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:49.7250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-25 06:46:49.7430000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:49.7430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:49.7490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-25 06:46:49.7690000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:49.7690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:49.7780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-25 06:46:49.8030000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-25 06:46:49.9670000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:49.9670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:49.9730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-25 06:46:50.1700000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-25 06:46:50.1710000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-25 06:46:59.6010000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-25 06:46:59.7720000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-25 06:46:59.7730000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:59.7730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:59.7780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 06:46:59.8620000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:59.8630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:59.8670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-25 06:46:59.8840000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:59.8840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:59.8880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-25 06:46:59.9020000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:59.9020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:59.9070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-25 06:46:59.9220000 [client] INFO Checking for ghcup installation +2024-06-25 06:46:59.9220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 06:46:59.9280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-25 06:47:00.0320000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-25 06:47:00.0330000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 06:47:00.0330000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 06:47:00.0330000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25 06:47:00.0330000 [client] INFO server environment variables: +2024-06-25 06:47:00.0330000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-25 06:47:00.0330000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-25 06:47:00.0330000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-25 06:47:00.0340000 [client] INFO Starting language server +2024-06-25T06:47:11.217464Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-25T06:47:11.219366Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25T06:47:11.219762Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T06:47:11.222612Z | Info | Logging heap statistics every 60.00s +2024-06-25T06:47:11.231483Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T06:47:11.232016Z | Info | Starting server +2024-06-25T06:47:11.249362Z | Info | Started LSP server in 0.02s +2024-06-25T06:47:12.541876Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-25T06:47:12.555856Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-06-25T06:47:12.556615Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-25T06:47:13.130160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-25T06:47:15.071306Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT9220-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-25T06:47:17.386058Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-25T06:47:17.391996Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-25T06:48:11.224137Z | Info | Live bytes: 49.27MB Heap size: 1207.96MB +2024-06-25T06:49:11.225296Z | Info | Live bytes: 49.33MB Heap size: 1207.96MB +2024-06-25T06:49:46.586441Z | Info | Reactor thread stopped +2024-06-25T06:49:46.604592Z | Error | Got EOF +2024-06-25 11:51:20.6610000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-25 11:51:20.6620000 [client] INFO Finding haskell-language-server +2024-06-25 11:51:20.6630000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:20.6640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:20.6690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-25 11:51:21.2380000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:21.2380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:21.2460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 11:51:21.3700000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:21.3700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:21.3770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-25 11:51:21.4810000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:21.4810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:21.4850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-25 11:51:21.5840000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:21.5850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:21.5880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-25 11:51:21.6010000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:21.6010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:21.6060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-25 11:51:21.6200000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:21.6200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:21.6230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-25 11:51:21.6440000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-25 11:51:21.7390000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:21.7390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:21.7420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-25 11:51:21.8250000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-25 11:51:21.8260000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-25 11:51:28.1450000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-25 11:51:28.5580000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-25 11:51:28.5590000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:28.5590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:28.5670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 11:51:28.6420000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:28.6420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:28.6470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-25 11:51:28.6630000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:28.6630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:28.6670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-25 11:51:28.6820000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:28.6820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:28.6880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-25 11:51:28.7040000 [client] INFO Checking for ghcup installation +2024-06-25 11:51:28.7040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 11:51:28.7100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-25 11:51:28.7970000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-25 11:51:28.7980000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 11:51:28.7980000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 11:51:28.7980000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25 11:51:28.7980000 [client] INFO server environment variables: +2024-06-25 11:51:28.7980000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-25 11:51:28.7980000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-25 11:51:28.7980000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-25 11:51:28.7990000 [client] INFO Starting language server +2024-06-25T11:51:38.300011Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-25T11:51:38.301570Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25T11:51:38.301761Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T11:51:38.304926Z | Info | Logging heap statistics every 60.00s +2024-06-25T11:51:38.317213Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T11:51:38.317604Z | Info | Starting server +2024-06-25T11:51:38.331770Z | Info | Started LSP server in 0.01s +2024-06-25T11:51:39.624135Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-25T11:51:39.636642Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-06-25T11:51:39.637656Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-25T11:51:40.211273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-25T11:51:41.733125Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT4810-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-25T11:51:43.678986Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-25T11:51:43.685634Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-25T11:52:38.306090Z | Info | Live bytes: 49.29MB Heap size: 1207.96MB +2024-06-25T11:53:38.307454Z | Info | Live bytes: 49.34MB Heap size: 1207.96MB +2024-06-25T11:53:48.762295Z | Info | Reactor thread stopped +2024-06-25T11:53:48.773761Z | Error | Got EOF +2024-06-25 13:19:18.0520000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-25 13:19:18.0530000 [client] INFO Finding haskell-language-server +2024-06-25 13:19:18.0540000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.0540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.0610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-25 13:19:18.4670000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.4670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.4720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 13:19:18.5780000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.5790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.5830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-25 13:19:18.7070000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.7070000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.7130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-25 13:19:18.8460000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.8460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.8510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-25 13:19:18.8650000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.8650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.8700000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-25 13:19:18.8830000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.8830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.8880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-25 13:19:18.9110000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-25 13:19:18.9490000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:18.9490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:18.9530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-25 13:19:19.0490000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-25 13:19:19.0500000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-25 13:19:24.9350000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-25 13:19:25.1850000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-25 13:19:25.1850000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:25.1850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:25.1900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 13:19:25.2750000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:25.2750000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:25.2800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-25 13:19:25.2980000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:25.2980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:25.3030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-25 13:19:25.3170000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:25.3170000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:25.3210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-25 13:19:25.3350000 [client] INFO Checking for ghcup installation +2024-06-25 13:19:25.3360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 13:19:25.3410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-25 13:19:25.4260000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-25 13:19:25.4270000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 13:19:25.4270000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 13:19:25.4270000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25 13:19:25.4270000 [client] INFO server environment variables: +2024-06-25 13:19:25.4270000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-25 13:19:25.4270000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-25 13:19:25.4270000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-25 13:19:25.4280000 [client] INFO Starting language server +2024-06-25T13:19:34.196621Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-25T13:19:34.197804Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25T13:19:34.198745Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T13:19:34.201772Z | Info | Logging heap statistics every 60.00s +2024-06-25T13:19:34.213593Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T13:19:34.214170Z | Info | Starting server +2024-06-25T13:19:34.216630Z | Info | Started LSP server in 0.00s +2024-06-25T13:19:35.378692Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-25T13:19:35.388525Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Sign.hs +2024-06-25T13:19:35.389464Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-25T13:19:35.958102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-25T13:19:37.484979Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT72180-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-25T13:19:39.279663Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-25T13:19:39.284125Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-25T13:19:47.496387Z | Info | Reactor thread stopped +2024-06-25T13:19:47.505727Z | Error | Got EOF +2024-06-25 16:31:35.2170000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-25 16:31:35.2190000 [client] INFO Finding haskell-language-server +2024-06-25 16:31:35.2220000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:35.2220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:35.2310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-25 16:31:36.8800000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:36.8800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:36.8900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 16:31:37.1380000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:37.1380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:37.1540000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-25 16:31:37.4450000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:37.4450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:37.4550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-25 16:31:37.7300000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:37.7310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:37.7380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.8.0.0' in cwd '/home/jordan' +2024-06-25 16:31:37.7560000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:37.7560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:37.7690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-25 16:31:37.7890000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:37.7890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:37.7980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-25 16:31:37.8280000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-25 16:31:37.8930000 [client] INFO Checking for ghcup installation +2024-06-25 16:31:37.8940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 16:31:37.9040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.8.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-25 16:31:38.1600000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-25 16:31:38.1610000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-25 19:27:54.5930000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-25 19:27:54.5930000 [client] INFO Finding haskell-language-server +2024-06-25 19:27:54.5940000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:54.5940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:54.6010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-25 19:27:54.9090000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:54.9090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:54.9160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 19:27:55.1570000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:55.1570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:55.1660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-25 19:27:55.3240000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:55.3240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:55.3300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-25 19:27:55.4910000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:55.4920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:55.4980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-25 19:27:55.5180000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:55.5180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:55.5240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-25 19:27:55.5400000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:55.5410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:55.5480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-25 19:27:55.5740000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-25 19:27:55.6200000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:55.6200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:55.6250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-25 19:27:55.7500000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-25 19:27:55.7510000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-25 19:27:59.0720000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-25 19:27:59.2730000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-25 19:27:59.2730000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:59.2730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:59.2780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-25 19:27:59.3740000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:59.3740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:59.3800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-25 19:27:59.4000000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:59.4000000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:59.4060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-25 19:27:59.4200000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:59.4200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:59.4240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-25 19:27:59.4380000 [client] INFO Checking for ghcup installation +2024-06-25 19:27:59.4380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-25 19:27:59.4420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-25 19:27:59.5500000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-25 19:27:59.5510000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 19:27:59.5510000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-25 19:27:59.5510000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25 19:27:59.5510000 [client] INFO server environment variables: +2024-06-25 19:27:59.5510000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-25 19:27:59.5510000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-25 19:27:59.5510000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-25 19:27:59.5530000 [client] INFO Starting language server +2024-06-25T19:28:12.188983Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-25T19:28:12.191088Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-25T19:28:12.191812Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T19:28:12.196765Z | Info | Logging heap statistics every 60.00s +2024-06-25T19:28:12.205137Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-25T19:28:12.205749Z | Info | Starting server +2024-06-25T19:28:12.218294Z | Info | Started LSP server in 0.01s +2024-06-25T19:28:13.637788Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-25T19:28:13.653604Z | Info | Cradle path: cardano-api/internal/Cardano/Api/TxIn.hs +2024-06-25T19:28:13.655335Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-25T19:28:14.171494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-25T19:28:16.307305Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT62237-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-25T19:28:18.600674Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-25T19:28:18.608777Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-25T19:29:12.198525Z | Info | Live bytes: 49.47MB Heap size: 1207.96MB +2024-06-25T19:30:12.199499Z | Info | Live bytes: 49.51MB Heap size: 1207.96MB +2024-06-25T19:31:12.200779Z | Info | Live bytes: 49.53MB Heap size: 1207.96MB +2024-06-25T19:32:12.202095Z | Info | Live bytes: 49.54MB Heap size: 1207.96MB +2024-06-25T19:33:12.203093Z | Info | Live bytes: 49.56MB Heap size: 1207.96MB +2024-06-25T19:34:12.204463Z | Info | Live bytes: 49.58MB Heap size: 1207.96MB +2024-06-25T19:35:12.205855Z | Info | Live bytes: 49.60MB Heap size: 1207.96MB +2024-06-25T19:36:12.206756Z | Info | Live bytes: 49.62MB Heap size: 1207.96MB +2024-06-25T19:37:12.207698Z | Info | Live bytes: 49.64MB Heap size: 1207.96MB +2024-06-25T19:38:12.209086Z | Info | Live bytes: 49.66MB Heap size: 1207.96MB +2024-06-25T19:39:12.209723Z | Info | Live bytes: 49.67MB Heap size: 1207.96MB +2024-06-25T19:39:31.852189Z | Info | Reactor thread stopped +2024-06-25T19:39:31.866610Z | Error | Got EOF +2024-06-26 07:15:54.0230000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-26 07:15:54.0240000 [client] INFO Finding haskell-language-server +2024-06-26 07:15:54.0250000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.0260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.0320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-26 07:15:54.3110000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.3120000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.3160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-26 07:15:54.4320000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.4320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.4360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-26 07:15:54.5510000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.5510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.5560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-26 07:15:54.6640000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.6650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.6690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-26 07:15:54.6840000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.6840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.6890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-26 07:15:54.7040000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.7040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.7100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-26 07:15:54.7290000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-26 07:15:54.8360000 [client] INFO Checking for ghcup installation +2024-06-26 07:15:54.8360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 07:15:54.8420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-26 07:15:54.9520000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-26 07:15:54.9520000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-26 12:39:00.3260000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-26 12:39:00.3270000 [client] INFO Finding haskell-language-server +2024-06-26 12:39:00.3270000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:00.3270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:00.3320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-26 12:39:00.6050000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:00.6050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:00.6110000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-26 12:39:00.7960000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:00.7960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:00.8020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-26 12:39:00.9280000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:00.9280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:00.9330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-26 12:39:01.0960000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:01.0960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:01.1010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-26 12:39:01.1190000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:01.1190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:01.1270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-26 12:39:01.1420000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:01.1420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:01.1480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-26 12:39:01.1700000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-26 12:39:01.2140000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:01.2140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:01.2210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-26 12:39:01.3470000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-26 12:39:01.3470000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-26 12:39:03.7920000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-26 12:39:03.8470000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-26 12:39:03.8470000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:03.8470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:03.8520000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-26 12:39:03.9480000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:03.9480000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:03.9550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-26 12:39:03.9760000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:03.9760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:03.9810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-26 12:39:03.9950000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:03.9950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:03.9990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-26 12:39:04.0140000 [client] INFO Checking for ghcup installation +2024-06-26 12:39:04.0140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-26 12:39:04.0190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-26 12:39:04.1260000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-26 12:39:04.1260000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-26 12:39:04.1260000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-26 12:39:04.1260000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-26 12:39:04.1260000 [client] INFO server environment variables: +2024-06-26 12:39:04.1260000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-26 12:39:04.1260000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-26 12:39:04.1260000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-26 12:39:04.1270000 [client] INFO Starting language server +2024-06-26T12:39:13.922841Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-26T12:39:13.923905Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-26T12:39:13.924119Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-26T12:39:13.926239Z | Info | Logging heap statistics every 60.00s +2024-06-26T12:39:13.933673Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-26T12:39:13.934336Z | Info | Starting server +2024-06-26T12:39:13.936183Z | Info | Started LSP server in 0.00s +2024-06-26T12:39:15.222499Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-26T12:39:15.235802Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/Expr.hs +2024-06-26T12:39:15.236821Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-26T12:39:15.803422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-26T12:39:17.619879Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT322173-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-26T12:39:19.594156Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-26T12:39:19.599130Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-26T12:40:13.927159Z | Info | Live bytes: 50.44MB Heap size: 1210.06MB +2024-06-26T12:41:13.927591Z | Info | Live bytes: 50.49MB Heap size: 1210.06MB +2024-06-26T12:42:13.929018Z | Info | Live bytes: 50.50MB Heap size: 1210.06MB +2024-06-26T12:43:13.930241Z | Info | Live bytes: 50.52MB Heap size: 1210.06MB +2024-06-26T12:43:39.868357Z | Info | Reactor thread stopped +2024-06-26T12:43:39.877362Z | Error | Got EOF +2024-06-27 07:35:21.7930000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-27 07:35:21.7940000 [client] INFO Finding haskell-language-server +2024-06-27 07:35:21.7960000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:21.7960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:21.8030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-27 07:35:22.0050000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:22.0050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:22.0090000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-27 07:35:22.1560000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:22.1560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:22.1600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-27 07:35:22.2860000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:22.2860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:22.2920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-27 07:35:22.4230000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:22.4230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:22.4280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-27 07:35:22.4450000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:22.4460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:22.4520000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-27 07:35:22.4690000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:22.4690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:22.4750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-27 07:35:22.4940000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-27 07:35:22.5400000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:22.5400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:22.5450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-27 07:35:22.6500000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-27 07:35:22.6500000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-27 07:35:33.1070000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-27 07:35:33.1930000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-27 07:35:33.1930000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:33.1930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:33.1990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-27 07:35:33.2740000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:33.2740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:33.2770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-27 07:35:33.2920000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:33.2920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:33.2960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-27 07:35:33.3090000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:33.3090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:33.3140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-27 07:35:33.3280000 [client] INFO Checking for ghcup installation +2024-06-27 07:35:33.3290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-27 07:35:33.3340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-27 07:35:33.4190000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-27 07:35:33.4190000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-27 07:35:33.4190000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-27 07:35:33.4190000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-27 07:35:33.4190000 [client] INFO server environment variables: +2024-06-27 07:35:33.4190000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-27 07:35:33.4190000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-27 07:35:33.4190000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-27 07:35:33.4200000 [client] INFO Starting language server +2024-06-27T07:35:42.411149Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-27T07:35:42.412813Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-27T07:35:42.413086Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-27T07:35:42.416204Z | Info | Logging heap statistics every 60.00s +2024-06-27T07:35:42.423929Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-27T07:35:42.424366Z | Info | Starting server +2024-06-27T07:35:42.436644Z | Info | Started LSP server in 0.01s +2024-06-27T07:35:43.560232Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-27T07:35:43.577690Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/Expr.hs +2024-06-27T07:35:43.579374Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-27T07:35:43.988607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-27T07:35:45.666195Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT12419-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-27T07:35:47.506414Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.48.0.1-inplace-internal-e086198af7ca5e47289221f1dcaba9d1e4fb8e32 +2024-06-27T07:35:47.511130Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.48.0.1-inplace-internal] +2024-06-27T07:35:59.497989Z | Info | Reactor thread stopped +2024-06-27T07:35:59.510451Z | Error | Got EOF +2024-06-28 07:39:02.1500000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-28 07:39:02.1520000 [client] INFO Finding haskell-language-server +2024-06-28 07:39:02.1540000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.1540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.1600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-28 07:39:02.3340000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.3340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.3380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 07:39:02.5210000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.5210000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.5270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-28 07:39:02.7020000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.7020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.7070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-28 07:39:02.8430000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.8430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.8490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-28 07:39:02.8710000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.8710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.8780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-28 07:39:02.8940000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.8940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.8990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-28 07:39:02.9170000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-28 07:39:02.9520000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:02.9520000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:02.9570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-28 07:39:03.0630000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-28 07:39:03.0640000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-28 07:39:13.4980000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-28 07:39:13.8330000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-28 07:39:13.8330000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:13.8340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:13.8420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 07:39:13.9180000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:13.9180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:13.9220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-28 07:39:13.9370000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:13.9370000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:13.9410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-28 07:39:13.9560000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:13.9560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:13.9620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-28 07:39:13.9770000 [client] INFO Checking for ghcup installation +2024-06-28 07:39:13.9770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 07:39:13.9830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-28 07:39:14.0680000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-28 07:39:14.0680000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 07:39:14.0680000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 07:39:14.0680000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28 07:39:14.0680000 [client] INFO server environment variables: +2024-06-28 07:39:14.0680000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-28 07:39:14.0680000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-28 07:39:14.0680000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-28 07:39:14.0690000 [client] INFO Starting language server +2024-06-28T07:39:41.599702Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-28T07:39:41.601552Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28T07:39:41.601788Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T07:39:41.604298Z | Info | Logging heap statistics every 60.00s +2024-06-28T07:39:41.612354Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T07:39:41.612757Z | Info | Starting server +2024-06-28T07:39:41.625296Z | Info | Started LSP server in 0.01s +2024-06-28T07:39:42.840104Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-28T07:39:42.857129Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query.hs +2024-06-28T07:39:42.858890Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T07:39:43.275549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T07:39:45.110229Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT8125-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T07:39:49.126730Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-4d29be51d13d6d402d60aa68419285148903b1ea +2024-06-28T07:39:49.132451Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-06-28T07:40:26.340816Z | Info | Reactor thread stopped +2024-06-28T07:40:26.350186Z | Error | Got EOF +2024-06-28T07:40:48.182064Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-28T07:40:48.182867Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28T07:40:48.183067Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T07:40:48.185358Z | Info | Logging heap statistics every 60.00s +2024-06-28T07:40:48.193264Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T07:40:48.193632Z | Info | Starting server +2024-06-28T07:41:48.247032Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:42:48.307869Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:43:48.366598Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:44:48.427652Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:45:48.488822Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:46:48.548937Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:47:48.551043Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:48:48.596867Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:49:48.657839Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:50:48.718627Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:51:48.752940Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:52:48.775786Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:53:48.836353Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:54:48.896923Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:55:48.939298Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:56:48.999863Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T07:57:17.456367Z | Error | Got EOF +2024-06-28 08:20:24.2650000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-28 08:20:24.2670000 [client] INFO Finding haskell-language-server +2024-06-28 08:20:24.2680000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:24.2680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:24.2760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-28 08:20:24.7190000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:24.7190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:24.7310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 08:20:24.8560000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:24.8570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:24.8620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-28 08:20:25.0170000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:25.0170000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:25.0240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-28 08:20:25.2090000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:25.2100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:25.2160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-28 08:20:25.2410000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:25.2410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:25.2470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-28 08:20:25.2640000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:25.2640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:25.2690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-28 08:20:25.2960000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-28 08:20:25.3470000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:25.3470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:25.3570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-28 08:20:25.4740000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-28 08:20:25.4750000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-28 08:20:33.6110000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-28 08:20:33.9950000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-28 08:20:33.9950000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:33.9960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:34.0010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 08:20:34.1160000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:34.1160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:34.1210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-28 08:20:34.1400000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:34.1400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:34.1460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-28 08:20:34.1600000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:34.1610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:34.1660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-28 08:20:34.1800000 [client] INFO Checking for ghcup installation +2024-06-28 08:20:34.1800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 08:20:34.1860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-28 08:20:34.3020000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-28 08:20:34.3020000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 08:20:34.3030000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 08:20:34.3030000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28 08:20:34.3030000 [client] INFO server environment variables: +2024-06-28 08:20:34.3030000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-28 08:20:34.3030000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-28 08:20:34.3030000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-28 08:20:34.3040000 [client] INFO Starting language server +2024-06-28T08:20:47.229939Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-28T08:20:47.230858Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28T08:20:47.231095Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T08:20:47.234367Z | Info | Logging heap statistics every 60.00s +2024-06-28T08:20:47.243659Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T08:20:47.244109Z | Info | Starting server +2024-06-28T08:20:47.245792Z | Info | Started LSP server in 0.00s +2024-06-28T08:20:48.799184Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-28T08:20:48.817002Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Convenience/Query.hs +2024-06-28T08:20:48.817836Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T08:20:49.330109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T08:20:51.536634Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT35780-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T08:20:53.364551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T08:20:53.897257Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-4d29be51d13d6d402d60aa68419285148903b1ea +2024-06-28T08:20:53.905726Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-06-28T08:20:54.203488Z | Info | Cradle path: cardano-api/src/Cardano/Api/Byron.hs +2024-06-28T08:20:54.204183Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T08:20:57.131069Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT35780-1 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T08:21:19.757406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T08:21:47.235336Z | Info | Live bytes: 42.23MB Heap size: 1162.87MB +2024-06-28T08:22:32.855032Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-2a1fafae868e53b22a4dc4076bd32b9fbe0b1e42 +2024-06-28T08:22:32.855330Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-2a1fafae868e53b22a4dc4076bd32b9fbe0b1e42 +2024-06-28T08:22:32.868775Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-8.49.0.0-inplace + , cardano-api-8.49.0.0-inplace-internal ] +2024-06-28T08:22:37.229259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T08:22:47.245843Z | Info | Live bytes: 103.65MB Heap size: 1317.01MB +2024-06-28T08:23:47.247271Z | Info | Live bytes: 118.53MB Heap size: 1317.01MB +2024-06-28T08:24:47.249406Z | Info | Live bytes: 118.55MB Heap size: 1317.01MB +2024-06-28T08:25:47.249871Z | Info | Live bytes: 118.97MB Heap size: 1317.01MB +2024-06-28T08:26:47.250549Z | Info | Live bytes: 119.40MB Heap size: 1317.01MB +2024-06-28T08:27:47.251198Z | Info | Live bytes: 119.41MB Heap size: 1317.01MB +2024-06-28T08:28:47.251907Z | Info | Live bytes: 119.43MB Heap size: 1317.01MB +2024-06-28T08:29:47.253439Z | Info | Live bytes: 119.86MB Heap size: 1317.01MB +2024-06-28T08:30:47.254221Z | Info | Live bytes: 119.87MB Heap size: 1317.01MB +2024-06-28T08:31:25.830145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T08:31:30.194888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T08:31:38.733911Z | Info | Reactor thread stopped +2024-06-28T08:31:38.770805Z | Error | Got EOF +2024-06-28T08:38:37.496221Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-28T08:38:37.497379Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28T08:38:37.497623Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T08:38:37.500146Z | Info | Logging heap statistics every 60.00s +2024-06-28T08:38:37.507804Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T08:38:37.508249Z | Info | Starting server +2024-06-28T08:39:37.561260Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:40:37.621812Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:41:37.682464Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:42:37.743211Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:43:37.803891Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:44:37.863811Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:45:37.924198Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:46:37.986011Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:47:38.046837Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:48:38.107536Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:49:38.168106Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:50:38.227854Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:51:38.233681Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:52:38.257071Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:53:38.316800Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:54:38.377725Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:55:38.413219Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:56:38.448001Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:57:38.511827Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:58:38.572073Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T08:59:38.632974Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:00:38.692899Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:01:38.752854Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:02:38.813820Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:03:38.876884Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:04:38.936840Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:05:38.973777Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:06:39.034242Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:07:39.060860Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:08:39.121497Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:09:39.162534Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:10:39.223071Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:11:39.282875Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:12:39.342893Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:13:39.402831Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:14:39.462823Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:15:39.522939Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:16:39.537831Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:17:39.588756Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:18:39.649029Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:19:39.709013Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:20:39.752789Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T09:21:14.154307Z | Error | Got EOF +2024-06-28 11:02:00.0330000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-28 11:02:00.0340000 [client] INFO Finding haskell-language-server +2024-06-28 11:02:00.0340000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.0350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.0410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-28 11:02:00.2060000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.2060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.2100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 11:02:00.3430000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.3430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.3480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-28 11:02:00.4530000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.4530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.4580000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-28 11:02:00.5890000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.5890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.5940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-28 11:02:00.6100000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.6100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.6160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-28 11:02:00.6310000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.6310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.6390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-28 11:02:00.7070000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-28 11:02:00.7500000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:00.7510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:00.7560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-28 11:02:00.8810000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-28 11:02:00.8820000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-28 11:02:07.1490000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-28 11:02:07.2070000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-28 11:02:07.2070000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:07.2070000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:07.2120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 11:02:07.2760000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:07.2760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:07.2800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-28 11:02:07.2960000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:07.2970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:07.3010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-28 11:02:07.3140000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:07.3140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:07.3180000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-28 11:02:07.3310000 [client] INFO Checking for ghcup installation +2024-06-28 11:02:07.3310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:02:07.3340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-28 11:02:07.4180000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-28 11:02:07.4180000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 11:02:07.4180000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 11:02:07.4180000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28 11:02:07.4180000 [client] INFO server environment variables: +2024-06-28 11:02:07.4180000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-28 11:02:07.4180000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-28 11:02:07.4180000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-28 11:02:07.4190000 [client] INFO Starting language server +2024-06-28T11:02:16.113085Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-28T11:02:16.114157Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28T11:02:16.114360Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T11:02:16.116723Z | Info | Logging heap statistics every 60.00s +2024-06-28T11:02:16.124793Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T11:02:16.125195Z | Info | Starting server +2024-06-28T11:02:16.127900Z | Info | Started LSP server in 0.00s +2024-06-28T11:02:17.373324Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-28T11:02:17.387091Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/Expr.hs +2024-06-28T11:02:17.388290Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T11:02:17.803506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T11:02:19.465595Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT202338-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T11:02:23.484173Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-8c21b1125296b624cdff3b207ac1358816749c79 +2024-06-28T11:02:23.490036Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-06-28T11:03:16.118274Z | Info | Live bytes: 54.82MB Heap size: 1218.45MB +2024-06-28T11:04:16.118894Z | Info | Live bytes: 54.87MB Heap size: 1218.45MB +2024-06-28T11:05:16.119859Z | Info | Live bytes: 54.89MB Heap size: 1218.45MB +2024-06-28T11:06:16.121002Z | Info | Live bytes: 54.91MB Heap size: 1218.45MB +2024-06-28T11:07:16.122364Z | Info | Live bytes: 54.94MB Heap size: 1218.45MB +2024-06-28T11:08:16.122889Z | Info | Live bytes: 54.96MB Heap size: 1218.45MB +2024-06-28T11:09:16.124241Z | Info | Live bytes: 54.98MB Heap size: 1218.45MB +2024-06-28T11:10:16.124851Z | Info | Live bytes: 55.00MB Heap size: 1218.45MB +2024-06-28T11:11:16.125780Z | Info | Live bytes: 55.02MB Heap size: 1218.45MB +2024-06-28T11:12:16.126343Z | Info | Live bytes: 55.49MB Heap size: 1218.45MB +2024-06-28T11:12:31.709210Z | Info | Reactor thread stopped +2024-06-28T11:12:31.724401Z | Error | Got EOF +2024-06-28 11:18:05.4560000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-28 11:18:05.4570000 [client] INFO Finding haskell-language-server +2024-06-28 11:18:05.4600000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:05.4600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:05.4670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-28 11:18:05.6750000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:05.6760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:05.6810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 11:18:05.7960000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:05.7970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:05.8030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-28 11:18:05.9360000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:05.9360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:05.9400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-28 11:18:06.0810000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:06.0820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:06.0860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-28 11:18:06.1010000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:06.1010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:06.1070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-28 11:18:06.1250000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:06.1250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:06.1310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-28 11:18:06.1500000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-28 11:18:06.1940000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:06.1940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:06.1990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-28 11:18:06.3420000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-28 11:18:06.3430000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-28 11:18:12.7880000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-28 11:18:12.8470000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-28 11:18:12.8470000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:12.8470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:12.8510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-28 11:18:12.9260000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:12.9260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:12.9300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-28 11:18:12.9460000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:12.9460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:12.9500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-28 11:18:12.9630000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:12.9630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:12.9670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-28 11:18:12.9800000 [client] INFO Checking for ghcup installation +2024-06-28 11:18:12.9800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-28 11:18:12.9840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-28 11:18:13.0680000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-28 11:18:13.0680000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 11:18:13.0680000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-28 11:18:13.0680000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28 11:18:13.0680000 [client] INFO server environment variables: +2024-06-28 11:18:13.0680000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-28 11:18:13.0680000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-28 11:18:13.0680000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-28 11:18:13.0690000 [client] INFO Starting language server +2024-06-28T11:18:22.380507Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-28T11:18:22.390625Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28T11:18:22.391016Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T11:18:22.394518Z | Info | Logging heap statistics every 60.00s +2024-06-28T11:18:22.402134Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T11:18:22.402519Z | Info | Starting server +2024-06-28T11:18:22.404200Z | Info | Started LSP server in 0.00s +2024-06-28T11:18:23.704651Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-28T11:18:23.719333Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/Expr.hs +2024-06-28T11:18:23.719990Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T11:18:24.284423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T11:18:26.102673Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT210195-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T11:18:27.987688Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-8c21b1125296b624cdff3b207ac1358816749c79 +2024-06-28T11:18:27.994355Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-06-28T11:19:22.399793Z | Info | Live bytes: 55.29MB Heap size: 1219.49MB +2024-06-28T11:20:22.400911Z | Info | Live bytes: 55.34MB Heap size: 1219.49MB +2024-06-28T11:21:22.402241Z | Info | Live bytes: 55.36MB Heap size: 1219.49MB +2024-06-28T11:22:22.402793Z | Info | Live bytes: 55.38MB Heap size: 1219.49MB +2024-06-28T11:22:35.318168Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/Expr.hs +2024-06-28T11:22:35.318596Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T11:22:38.041323Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT210195-1 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T11:22:42.133491Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-4d29be51d13d6d402d60aa68419285148903b1ea +2024-06-28T11:22:42.136903Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-06-28T11:22:42.400659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T11:22:47.426433Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/Expr.hs +2024-06-28T11:22:47.426803Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T11:22:47.978934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T11:22:49.584867Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT210195-2 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T11:22:53.601705Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-4d29be51d13d6d402d60aa68419285148903b1ea +2024-06-28T11:22:53.604588Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-06-28T11:23:00.111501Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/Expr.hs +2024-06-28T11:23:00.112335Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-28T11:23:00.662181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T11:23:19.752548Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT210195-3 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-28T11:23:20.348136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-28T11:23:22.404244Z | Info | Live bytes: 58.96MB Heap size: 1296.04MB +2024-06-28T11:23:34.524105Z | Info | Reactor thread stopped +2024-06-28T11:23:34.535039Z | Error | Got EOF +2024-06-28T11:24:21.867591Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-28T11:24:21.868447Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-28T11:24:21.868865Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T11:24:21.871271Z | Info | Logging heap statistics every 60.00s +2024-06-28T11:24:21.878846Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-28T11:24:21.879147Z | Info | Starting server +2024-06-28T11:25:21.932610Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:26:21.993208Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:27:22.005050Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:28:22.065855Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:29:22.126750Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:30:22.187551Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:31:22.248259Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:32:22.308924Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:33:22.369744Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:34:22.373736Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:35:22.434411Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:36:22.495163Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:37:22.554347Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:38:22.565695Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:39:22.613656Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:40:22.674518Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:41:22.735186Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:42:22.795961Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:43:22.856543Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:44:22.917253Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:45:22.925626Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:46:22.940789Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:47:22.959259Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:48:23.019986Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:49:23.080800Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:50:23.115519Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:51:23.176227Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:52:23.236972Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:53:23.258189Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:54:23.319176Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:55:23.373172Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:56:23.433451Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:57:23.471477Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:58:23.510936Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T11:59:23.511847Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:00:23.572415Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:01:23.587238Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:02:23.648450Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:03:23.664138Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:04:23.723427Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:30:52.406615Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:31:52.457653Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:32:52.508469Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:33:52.515208Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:34:52.533191Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:35:52.538750Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:36:52.599304Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:37:52.642577Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:38:52.702597Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:39:52.722254Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:40:52.782770Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:41:52.815419Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:42:52.839537Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:43:52.900229Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:44:52.960832Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:45:53.021481Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:46:53.082195Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:47:53.142946Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:48:53.203592Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:49:53.227077Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:50:53.236810Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:51:53.296530Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:52:53.356673Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:53:53.414706Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:54:53.475358Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:55:53.518300Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:56:53.519247Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:57:53.526878Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:58:53.587720Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T12:59:53.647566Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:00:53.708229Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:01:53.768865Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:02:53.829589Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:03:53.890346Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:04:53.951039Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:05:53.972664Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:06:53.984198Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:07:54.044769Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:08:54.105598Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:09:54.166408Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:10:54.205723Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:11:54.266304Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:12:54.269718Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:13:54.330351Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:14:54.333807Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:15:54.365744Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:16:54.425691Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:17:54.429780Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:18:54.490414Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:19:54.550965Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:20:54.611656Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:21:54.621833Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:22:54.682458Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:23:54.685765Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:24:54.746439Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:25:54.786027Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:26:54.846627Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:27:54.877798Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:28:54.933761Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:29:54.994439Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:30:55.046459Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:31:55.107083Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:32:55.167526Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:33:55.168991Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:34:55.182226Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:35:55.190320Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:36:55.219538Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:37:55.261727Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:38:55.321696Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:39:55.336413Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:40:55.396970Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:41:55.457511Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:42:55.518066Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:43:55.578621Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:44:55.639100Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:45:55.673594Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:46:55.733704Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:47:55.743853Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:48:55.804497Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:49:55.865152Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:50:55.925951Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:51:55.951724Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:52:55.981334Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:53:56.040998Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:54:56.101520Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:55:56.161746Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:56:56.222655Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:57:56.283339Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:58:56.343838Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T13:59:56.404416Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:00:56.465062Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:01:56.503411Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:02:56.509698Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:03:56.570260Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:04:56.630926Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:05:56.669766Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:06:56.705765Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-06-28T14:07:19.246915Z | Error | Got EOF +2024-06-29 16:30:11.6910000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-29 16:30:11.6920000 [client] INFO Finding haskell-language-server +2024-06-29 16:30:11.6940000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:11.6940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:11.7020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-29 16:30:12.0750000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:12.0750000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:12.0810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-29 16:30:12.2630000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:12.2640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:12.2690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-29 16:30:12.3940000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:12.3940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:12.3990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-29 16:30:12.5560000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:12.5560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:12.5630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-29 16:30:12.5790000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:12.5790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:12.5840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-29 16:30:12.6030000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:12.6030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:12.6080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-29 16:30:12.6320000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-29 16:30:12.7730000 [client] INFO Checking for ghcup installation +2024-06-29 16:30:12.7730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-29 16:30:12.7800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-29 16:30:12.9260000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-29 16:30:12.9270000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-30 17:16:51.6250000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-06-30 17:16:51.6260000 [client] INFO Finding haskell-language-server +2024-06-30 17:16:51.6270000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:51.6270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:51.6340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-06-30 17:16:52.0080000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:52.0080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:52.0130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-30 17:16:52.1840000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:52.1840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:52.1910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-06-30 17:16:52.3070000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:52.3070000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:52.3120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-06-30 17:16:52.5300000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:52.5310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:52.5360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-06-30 17:16:52.5660000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:52.5660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:52.5740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-06-30 17:16:52.5890000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:52.5900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:52.5950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-06-30 17:16:52.6140000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-06-30 17:16:52.6610000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:52.6610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:52.6680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-06-30 17:16:52.7840000 [client] INFO Working out the project GHC version. This might take a while... +2024-06-30 17:16:52.7850000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-06-30 17:16:55.5080000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-06-30 17:16:55.5690000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-06-30 17:16:55.5690000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:55.5700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:55.5780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-06-30 17:16:55.6840000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:55.6840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:55.6910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-06-30 17:16:55.7150000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:55.7150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:55.7260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-06-30 17:16:55.7430000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:55.7430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:55.7490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-06-30 17:16:55.7660000 [client] INFO Checking for ghcup installation +2024-06-30 17:16:55.7660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-06-30 17:16:55.7740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-06-30 17:16:55.9500000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-06-30 17:16:55.9510000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-30 17:16:55.9510000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-06-30 17:16:55.9510000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-30 17:16:55.9520000 [client] INFO server environment variables: +2024-06-30 17:16:55.9520000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-06-30 17:16:55.9520000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-06-30 17:16:55.9520000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-06-30 17:16:55.9550000 [client] INFO Starting language server +2024-06-30T17:17:08.795461Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-06-30T17:17:08.798076Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-06-30T17:17:08.798424Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-30T17:17:08.803880Z | Info | Logging heap statistics every 60.00s +2024-06-30T17:17:08.817845Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-06-30T17:17:08.818335Z | Info | Starting server +2024-06-30T17:17:08.833280Z | Info | Started LSP server in 0.02s +2024-06-30T17:17:10.353183Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-06-30T17:17:10.369171Z | Info | Cradle path: cardano-api/internal/Cardano/Api/IPC.hs +2024-06-30T17:17:10.370323Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-06-30T17:17:10.883539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-30T17:17:10.883708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-06-30T17:17:13.173534Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT18408-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-06-30T17:17:18.653716Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-cddf488ead73683b2fb306851466f8cd4a229cb7 +2024-06-30T17:17:18.660085Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-06-30T17:18:08.809456Z | Info | Live bytes: 64.78MB Heap size: 1229.98MB +2024-06-30T17:19:08.810726Z | Info | Live bytes: 64.82MB Heap size: 1229.98MB +2024-06-30T17:20:08.812029Z | Info | Live bytes: 64.84MB Heap size: 1229.98MB +2024-06-30T17:21:08.813207Z | Info | Live bytes: 64.85MB Heap size: 1229.98MB +2024-06-30T17:22:08.814672Z | Info | Live bytes: 64.87MB Heap size: 1229.98MB +2024-06-30T17:23:08.815734Z | Info | Live bytes: 64.88MB Heap size: 1229.98MB +2024-06-30T17:24:08.816235Z | Info | Live bytes: 64.90MB Heap size: 1229.98MB +2024-06-30T17:25:08.817616Z | Info | Live bytes: 64.91MB Heap size: 1229.98MB +2024-06-30T17:26:08.818061Z | Info | Live bytes: 64.93MB Heap size: 1229.98MB +2024-06-30T17:27:08.818940Z | Info | Live bytes: 64.94MB Heap size: 1229.98MB +2024-06-30T17:28:08.819452Z | Info | Live bytes: 64.96MB Heap size: 1229.98MB +2024-06-30T17:29:08.820089Z | Info | Live bytes: 64.97MB Heap size: 1229.98MB +2024-06-30T17:30:08.821368Z | Info | Live bytes: 64.98MB Heap size: 1229.98MB +2024-06-30T17:31:08.822075Z | Info | Live bytes: 65.00MB Heap size: 1229.98MB +2024-06-30T17:32:08.823394Z | Info | Live bytes: 65.01MB Heap size: 1229.98MB +2024-06-30T17:33:08.823921Z | Info | Live bytes: 65.03MB Heap size: 1229.98MB +2024-06-30T17:34:08.825393Z | Info | Live bytes: 65.04MB Heap size: 1229.98MB +2024-06-30T17:35:08.826563Z | Info | Live bytes: 65.06MB Heap size: 1229.98MB +2024-06-30T17:36:08.827494Z | Info | Live bytes: 65.07MB Heap size: 1229.98MB +2024-06-30T17:37:08.828085Z | Info | Live bytes: 65.08MB Heap size: 1229.98MB +2024-06-30T17:38:08.829772Z | Info | Live bytes: 65.10MB Heap size: 1229.98MB +2024-06-30T17:39:08.831778Z | Info | Live bytes: 65.11MB Heap size: 1229.98MB +2024-06-30T17:40:08.833532Z | Info | Live bytes: 65.12MB Heap size: 1229.98MB +2024-06-30T17:41:08.834868Z | Info | Live bytes: 65.13MB Heap size: 1229.98MB +2024-06-30T17:42:08.836308Z | Info | Live bytes: 65.14MB Heap size: 1229.98MB +2024-06-30T17:43:08.836912Z | Info | Live bytes: 65.16MB Heap size: 1229.98MB +2024-06-30T17:44:08.839102Z | Info | Live bytes: 65.17MB Heap size: 1229.98MB +2024-06-30T17:45:08.840193Z | Info | Live bytes: 65.18MB Heap size: 1229.98MB +2024-06-30T17:46:08.841145Z | Info | Live bytes: 65.20MB Heap size: 1229.98MB +2024-06-30T17:47:08.841632Z | Info | Live bytes: 65.21MB Heap size: 1229.98MB +2024-06-30T17:48:08.842415Z | Info | Live bytes: 65.22MB Heap size: 1229.98MB +2024-06-30T17:49:08.844031Z | Info | Live bytes: 65.24MB Heap size: 1229.98MB +2024-06-30T17:50:08.844952Z | Info | Live bytes: 65.24MB Heap size: 1229.98MB +2024-06-30T17:51:08.845850Z | Info | Live bytes: 65.26MB Heap size: 1229.98MB +2024-06-30T17:52:08.848073Z | Info | Live bytes: 65.27MB Heap size: 1229.98MB +2024-06-30T17:53:08.849559Z | Info | Live bytes: 65.29MB Heap size: 1229.98MB +2024-06-30T17:54:08.850354Z | Info | Live bytes: 65.30MB Heap size: 1229.98MB +2024-06-30T17:55:08.851446Z | Info | Live bytes: 65.31MB Heap size: 1229.98MB +2024-06-30T17:56:08.852408Z | Info | Live bytes: 65.33MB Heap size: 1229.98MB +2024-06-30T17:57:08.853198Z | Info | Live bytes: 469.47MB Heap size: 1976.57MB +2024-06-30T17:58:08.903338Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T17:59:08.963912Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:00:09.024528Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:01:09.084967Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:02:09.089149Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:03:09.105895Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:04:09.166402Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:05:09.227035Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:06:09.287645Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:07:09.298291Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:08:09.357776Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:09:09.418264Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:10:09.445736Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:11:09.506262Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:12:09.565739Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:13:09.582822Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:14:09.642732Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:15:09.703045Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:16:09.763860Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:17:09.823937Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:18:09.883748Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:19:09.943802Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:20:10.003853Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:21:10.064360Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:22:10.123926Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:23:10.183927Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:24:10.243873Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:25:10.298560Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:26:10.359048Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:27:10.418748Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:28:10.456785Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:29:10.516851Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:30:10.526314Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:31:10.586866Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:32:10.647536Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:33:10.665462Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:34:10.726122Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:35:10.740744Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:36:10.791541Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:37:10.851891Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:38:10.911785Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:39:10.972301Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:40:11.032968Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:41:11.093677Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:42:11.125637Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:43:11.185741Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:44:11.245736Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:45:11.314986Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:46:11.375645Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:47:11.378756Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:48:11.439369Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:49:11.498598Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:50:11.560773Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:51:11.620845Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:52:11.681396Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:53:11.741904Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:54:11.801741Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:55:11.862021Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:56:11.922036Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:57:11.938543Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:58:11.966951Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T18:59:12.026883Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T19:00:12.042716Z | Info | Live bytes: 692.13MB Heap size: 1976.57MB +2024-06-30T19:00:46.658220Z | Error | Got EOF +2024-06-30T19:00:46.658516Z | Info | Reactor thread stopped +2024-06-30T19:00:46.658763Z | Error | ReactorThreadException +: hPutChar: resource vanished (Broken pipe) +2024-07-01 08:51:38.1840000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-01 08:51:38.1940000 [client] INFO Finding haskell-language-server +2024-07-01 08:51:38.1950000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:38.1950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:38.2010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-01 08:51:38.5390000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:38.5400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:38.5450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-01 08:51:38.6810000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:38.6820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:38.6880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-01 08:51:38.8030000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:38.8030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:38.8080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-01 08:51:38.9590000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:38.9590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:38.9650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-01 08:51:38.9790000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:38.9790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:38.9860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-01 08:51:39.0020000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:39.0020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:39.0070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-01 08:51:39.0270000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-01 08:51:39.0740000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:39.0740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:39.0800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-01 08:51:39.1850000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-01 08:51:39.1860000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-01 08:51:45.7920000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-07-01 08:51:45.8690000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-01 08:51:45.8690000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:45.8690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:45.8770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-01 08:51:45.9530000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:45.9530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:45.9570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-01 08:51:45.9740000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:45.9740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:45.9780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-07-01 08:51:45.9910000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:45.9910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:45.9960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-07-01 08:51:46.0090000 [client] INFO Checking for ghcup installation +2024-07-01 08:51:46.0090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 08:51:46.0140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-07-01 08:51:46.1080000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-01 08:51:46.1090000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-01 08:51:46.1090000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-01 08:51:46.1090000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01 08:51:46.1090000 [client] INFO server environment variables: +2024-07-01 08:51:46.1090000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-01 08:51:46.1090000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-01 08:51:46.1090000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-01 08:51:46.1100000 [client] INFO Starting language server +2024-07-01T08:51:54.921892Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-07-01T08:51:54.923080Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01T08:51:54.923485Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T08:51:54.926383Z | Info | Logging heap statistics every 60.00s +2024-07-01T08:51:54.932704Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T08:51:54.933044Z | Info | Starting server +2024-07-01T08:51:54.934883Z | Info | Started LSP server in 0.00s +2024-07-01T08:51:56.087406Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-01T08:51:56.098814Z | Info | Cradle path: cardano-api/internal/Cardano/Api/IPC.hs +2024-07-01T08:51:56.099426Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T08:51:56.675448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T08:51:56.675492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T08:51:58.311532Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT43093-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-07-01T08:52:00.132225Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-cddf488ead73683b2fb306851466f8cd4a229cb7 +2024-07-01T08:52:00.138235Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-01T08:52:20.029320Z | Error | Got EOF +2024-07-01 09:14:31.3040000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-01 09:14:31.3050000 [client] INFO Finding haskell-language-server +2024-07-01 09:14:31.3060000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.3060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.3120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-01 09:14:31.4270000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.4270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.4310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-01 09:14:31.6010000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.6020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.6070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-01 09:14:31.7330000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.7330000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.7380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-01 09:14:31.8490000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.8490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.8540000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-01 09:14:31.8710000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.8720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.8780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-01 09:14:31.8960000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.8970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.9020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-01 09:14:31.9200000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-01 09:14:31.9650000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:31.9650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:31.9700000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-01 09:14:32.1280000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-01 09:14:32.1280000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-01 09:14:38.7300000 [client] INFO The GHC version for the project or file: 9.6.4 +2024-07-01 09:14:38.8080000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-01 09:14:38.8080000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:38.8080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:38.8170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-01 09:14:38.8930000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:38.8930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:38.8970000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-01 09:14:38.9130000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:38.9130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:38.9170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.7.0.0' in cwd '/home/jordan' +2024-07-01 09:14:38.9310000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:38.9310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:38.9360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.4' in cwd '/home/jordan' +2024-07-01 09:14:38.9500000 [client] INFO Checking for ghcup installation +2024-07-01 09:14:38.9510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:14:38.9550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.7.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.4 --install' in cwd '/home/jordan' +2024-07-01 09:14:39.0500000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-01 09:14:39.0500000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-01 09:14:39.0500000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-01 09:14:39.0500000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01 09:14:39.0500000 [client] INFO server environment variables: +2024-07-01 09:14:39.0500000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-01 09:14:39.0500000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-01 09:14:39.0500000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.4_cabal-3.10.3.0_hls-2.7.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-01 09:14:39.0510000 [client] INFO Starting language server +2024-07-01T09:14:47.855364Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-07-01T09:14:47.856207Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01T09:14:47.856374Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:14:47.859039Z | Info | Logging heap statistics every 60.00s +2024-07-01T09:14:47.865623Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:14:47.865968Z | Info | Starting server +2024-07-01T09:14:47.867436Z | Info | Started LSP server in 0.00s +2024-07-01T09:14:49.024887Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-01T09:14:49.043564Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs +2024-07-01T09:14:49.044620Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T09:14:49.613119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:14:51.185677Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT65168-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-07-01T09:14:52.973919Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-cddf488ead73683b2fb306851466f8cd4a229cb7 +2024-07-01T09:14:52.979239Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-01T09:15:47.860824Z | Info | Live bytes: 57.25MB Heap size: 1219.49MB +2024-07-01T09:16:36.676915Z | Info | Reactor thread stopped +2024-07-01T09:16:36.688103Z | Error | Got EOF +2024-07-01T09:17:49.980012Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-07-01T09:17:49.981101Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01T09:17:49.981402Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:17:49.984001Z | Info | Logging heap statistics every 60.00s +2024-07-01T09:17:49.992655Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:17:49.993063Z | Info | Starting server +2024-07-01T09:18:50.036327Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:19:50.096728Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:20:50.156786Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:21:50.216778Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:22:50.276791Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:23:50.337265Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:24:50.397806Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:25:50.433658Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:26:50.493709Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:27:50.553635Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:28:50.565963Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:29:50.625607Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-01T09:30:18.872652Z | Info | Started LSP server in 12m29s +2024-07-01T09:30:20.057316Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-01T09:30:20.064945Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs +2024-07-01T09:30:20.066035Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T09:30:20.635756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:30:22.209126Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT67514-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-07-01T09:30:24.047604Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-cddf488ead73683b2fb306851466f8cd4a229cb7 +2024-07-01T09:30:24.052263Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-01T09:30:45.677762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:30:49.890054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:30:50.627202Z | Info | Live bytes: 82.08MB Heap size: 1219.49MB +2024-07-01T09:31:07.795491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:31:13.511518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:31:14.153103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:31:15.378012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:31:16.488351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:31:38.950529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:31:50.627883Z | Info | Live bytes: 120.77MB Heap size: 1281.36MB +2024-07-01T09:31:54.632458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:32:50.628975Z | Info | Live bytes: 95.89MB Heap size: 1310.72MB +2024-07-01T09:32:51.416811Z | Info | Reactor thread stopped +2024-07-01T09:32:51.428305Z | Error | Got EOF +2024-07-01T09:34:20.296931Z | Info | haskell-language-server version: 2.7.0.0 (GHC: 9.6.4) (PATH: /home/jordan/.ghcup/hls/2.7.0.0/lib/haskell-language-server-2.7.0.0/bin/haskell-language-server-9.6.4) +2024-07-01T09:34:20.297740Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01T09:34:20.297974Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:34:20.300500Z | Info | Logging heap statistics every 60.00s +2024-07-01T09:34:20.308373Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , retrie + , ghcide-completions + , alternateNumberFormat + , ghcide-code-actions-bindings + , explicit-fields + , ghcide-hover-and-symbols + , ghcide-code-actions-type-signatures + , semanticTokens + , floskell + , fourmolu + , ghcide-extend-import-action + , ghcide-code-actions-fill-holes + , importLens + , LSPRecorderCallback + , cabal + , qualifyImportedNames + , moduleName + , splice + , stylish-haskell + , changeTypeSignature + , hlint + , class + , ormolu + , callHierarchy + , stan + , ghcide-type-lenses + , codeRange + , cabal-fmt + , eval + , rename + , ghcide-code-actions-imports-exports + , gadt + , overloaded-record-dot + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:34:20.308879Z | Info | Starting server +2024-07-01T09:34:20.310392Z | Info | Started LSP server in 0.00s +2024-07-01T09:34:21.619012Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri 1263931185920218589 "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-01T09:34:21.728816Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs +2024-07-01T09:34:21.729907Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T09:34:23.956317Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-8c94ef80578cdf6bbdd2b600ce2e754c cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT97824-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/bin/ghc-9.6.4 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.4/lib/ghc-9.6.4/lib +2024-07-01T09:34:28.254301Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-cddf488ead73683b2fb306851466f8cd4a229cb7 +2024-07-01T09:34:28.259588Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-01T09:34:32.980092Z | Info | Reactor thread stopped +2024-07-01T09:34:32.987364Z | Error | Got EOF +2024-07-01 09:37:07.2000000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-01 09:37:07.2010000 [client] INFO Finding haskell-language-server +2024-07-01 09:37:07.2020000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.2020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.2070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-01 09:37:07.3020000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.3020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.3080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-01 09:37:07.4390000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.4390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.4440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-01 09:37:07.5720000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.5730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.5770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-01 09:37:07.6650000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.6650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.6710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-01 09:37:07.6850000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.6850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.6900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-01 09:37:07.7050000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.7050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.7100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-01 09:37:07.7270000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-01 09:37:07.7600000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:07.7600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:07.7650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-01 09:37:07.8510000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-01 09:37:07.8520000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-01 09:37:30.2450000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-01 09:37:30.3570000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-01 09:37:30.3570000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:30.3570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:30.3630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-01 09:37:30.4380000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:30.4380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:30.4420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-01 09:37:30.4580000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:30.4580000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:30.4630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-01 09:37:30.4780000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:30.4780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:30.4840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-01 09:37:30.4990000 [client] INFO Checking for ghcup installation +2024-07-01 09:37:30.4990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-01 09:37:30.5040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-01 09:37:30.6100000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-01 09:37:30.6100000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-01 09:37:30.6100000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-01 09:37:30.6100000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01 09:37:30.6100000 [client] INFO server environment variables: +2024-07-01 09:37:30.6100000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-01 09:37:30.6100000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-01 09:37:30.6100000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-01 09:37:30.6110000 [client] INFO Starting language server +2024-07-01T09:37:40.066453Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-01T09:37:40.067726Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01T09:37:40.067955Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:37:40.070406Z | Info | Logging heap statistics every 60.00s +2024-07-01T09:37:40.077414Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T09:37:40.078004Z | Info | Starting server +2024-07-01T09:37:40.092194Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-01T09:37:40.178760Z | Info | Started LSP server in 0.10s +2024-07-01T09:37:41.472550Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs +2024-07-01T09:37:41.473289Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T09:37:42.840449Z | Info | Load cabal cradle using single file +2024-07-01T09:37:43.792790Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT100497-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-01T09:37:49.958118Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-57be9437b2c911e2f75d7c43930aaaa83fcf6215 +2024-07-01T09:37:49.963406Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-01T09:38:40.111697Z | Info | Live bytes: 696.67MB Heap size: 1885.34MB +2024-07-01T09:39:40.154223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:39:40.168736Z | Info | Live bytes: 696.67MB Heap size: 1885.34MB +2024-07-01T09:39:43.799944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:39:44.685578Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T09:39:48.126539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:39:48.557209Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T09:39:54.248453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:39:55.936805Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T09:39:59.126249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:12.610510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:19.634382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:21.281832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:29.951955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:40.178801Z | Info | Live bytes: 640.13MB Heap size: 2416.97MB +2024-07-01T09:40:41.204725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:42.418317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:40:42.581009Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:40:42.635270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:40:42.683712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:40:42.730512Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:40:42.798511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:43.319613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:43.607145Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T09:40:44.270021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:49.999307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:50.592102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:51.613188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:57.948494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:40:59.789234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:00.968178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:01.503804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:04.413392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:11.091777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:29.110855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:30.532106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:31.400231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:36.838421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:40.183838Z | Info | Live bytes: 712.28MB Heap size: 2416.97MB +2024-07-01T09:41:51.155603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:41:51.681966Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" ] +2024-07-01T09:41:53.158719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:05.376155Z | Info | Cradle path: cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs +2024-07-01T09:42:05.376965Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T09:42:05.418264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:06.994791Z | Info | Load cabal cradle using single file +2024-07-01T09:42:08.020644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:08.055829Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:gen + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT100497-211 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-01T09:42:10.954336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:11.788323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:11.848808Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T09:42:12.513025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:18.842260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:22.076320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:22.968374Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" ] +2024-07-01T09:42:23.211407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:24.687989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:32.596559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:33.188121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:38.792859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:39.378491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:40.185437Z | Info | Live bytes: 936.75MB Heap size: 2416.97MB +2024-07-01T09:42:42.333441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:42.896258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:43.409561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:43.983668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:44.629458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:44.999809Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T09:42:50.352500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:50.919263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:51.485824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:53.943776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:54.450383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:55.350914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:42:59.096954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:03.619620Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:06.760425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:08.898927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:14.199073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:15.661566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:15.879254Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:15.915574Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:15.990280Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:16.117688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:16.945660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:19.100461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:20.430384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:20.652864Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T09:43:21.328345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:40.204756Z | Info | Live bytes: 1131.74MB Heap size: 2416.97MB +2024-07-01T09:43:41.472580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:49.717381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:49.886270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:50.004678Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:50.167962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:53.713714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:53.840572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:53.957205Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:43:54.142912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:43:54.675356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:44:23.599109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:44:24.670892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:44:24.785523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:44:24.868595Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:44:24.981510Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:44:25.135328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:44:25.796514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:44:26.291982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:44:26.624800Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T09:44:40.219014Z | Info | Live bytes: 1200.25MB Heap size: 2416.97MB +2024-07-01T09:45:40.279768Z | Info | Live bytes: 1200.25MB Heap size: 2416.97MB +2024-07-01T09:46:40.340776Z | Info | Live bytes: 1200.25MB Heap size: 2416.97MB +2024-07-01T09:47:40.402037Z | Info | Live bytes: 1200.25MB Heap size: 2416.97MB +2024-07-01T09:48:38.014318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:48:40.403853Z | Info | Live bytes: 664.53MB Heap size: 2877.29MB +2024-07-01T09:48:54.797180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:49:40.449622Z | Info | Live bytes: 669.76MB Heap size: 2877.29MB +2024-07-01T09:49:52.955639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:18.414656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:19.657241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:21.491119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:22.174058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:22.715241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:26.345414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:26.586840Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:50:26.810057Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:50:26.994393Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:50:27.021537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:27.539792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:28.124957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:28.671174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:37.409118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:40.452915Z | Info | Live bytes: 690.90MB Heap size: 2877.29MB +2024-07-01T09:50:43.272504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:47.716281Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:50:48.132165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:48.738411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:50:48.987767Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:50:49.162024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:50:49.198227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:49.938625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:50.468698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:51.266504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:53.068167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:53.583499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:54.241302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:55.110197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:55.833960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:56.702222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:50:57.279977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:02.449286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:02.477603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:02.532548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:02.761911Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:02.993696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:03.096874Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:04.635148Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:04.972580Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:05.097017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:17.306415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:40.477628Z | Info | Live bytes: 699.28MB Heap size: 2877.29MB +2024-07-01T09:51:56.108211Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:56.158771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:56.312312Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:56.350430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:56.403402Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:56.570671Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:56.667062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:57.033919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:59.155487Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:59.198425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:59.333044Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:59.372162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:51:59.423722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:59.599206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:59.680935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:51:59.884438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:11.106673Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:11.177233Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:11.345516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:11.412890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:11.560873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:11.593148Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:11.669419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:12.129480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:17.899563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:17.947937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:17.958639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:18.530239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:18.692732Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:18.915385Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:18.998091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:19.062976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:19.527630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:20.079693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:20.952467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:22.890255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:23.783349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:28.437794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:40.489727Z | Info | Live bytes: 727.75MB Heap size: 2877.29MB +2024-07-01T09:52:42.542186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:42.668156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:43.542201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:52:58.667607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:52:59.109463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:53:09.412170Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:53:09.863153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:53:11.013293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:53:12.646135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:53:13.608773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:53:40.517743Z | Info | Live bytes: 738.11MB Heap size: 2877.29MB +2024-07-01T09:54:40.553105Z | Info | Live bytes: 738.11MB Heap size: 2877.29MB +2024-07-01T09:54:45.553987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:54:46.015508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:01.343612Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T09:55:40.584787Z | Info | Live bytes: 738.11MB Heap size: 2877.29MB +2024-07-01T09:55:46.086223Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:46.293869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:46.348708Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:46.766063Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:46.815199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:46.862310Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:47.041910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:47.138976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:47.193656Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:47.324735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:47.605095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:47.659809Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:47.853412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:47.881659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:48.006339Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:48.292649Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:48.472507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:48.612696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:49.076585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:49.653719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:51.158684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:51.536751Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:51.752261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:53.483619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:54.049348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:55.440261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:56.590429Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:56.790110Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:56.834451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:57.480634Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:57.803150Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:57.904080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:57.946812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:55:58.688633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:58.800320Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:58.886552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:59.011606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:55:59.153751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:00.851795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:05.170493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:05.871016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:05.923286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:06.096536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:06.194852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:06.266832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:06.320150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:11.287430Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:11.451520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:11.532415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:11.616460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:11.735000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:12.297936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:12.521996Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:12.637389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:12.708863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:12.754128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:12.805913Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:56:13.265763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:13.873143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:56:40.612816Z | Info | Live bytes: 794.83MB Heap size: 2877.29MB +2024-07-01T09:57:34.714799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:57:35.746017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:57:36.199350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:57:37.186769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:57:37.812717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:57:37.933570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:57:40.615766Z | Info | Live bytes: 794.23MB Heap size: 2877.29MB +2024-07-01T09:57:42.114684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:57:48.700999Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T09:58:40.636827Z | Info | Live bytes: 810.13MB Heap size: 2877.29MB +2024-07-01T09:59:28.638028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:59:29.240467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:29.371959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:29.482017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:29.572104Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:29.648421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:29.698132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:59:30.090219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:30.139176Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:30.212712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:59:30.339485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:30.403791Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:30.640283Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:30.756261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T09:59:30.805434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:59:32.652870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:59:34.477943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:59:36.190559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T09:59:40.642966Z | Info | Live bytes: 804.61MB Heap size: 2877.29MB +2024-07-01T10:00:01.696142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:00:02.305500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:00:02.729197Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:00:39.443803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:00:40.644853Z | Info | Live bytes: 824.87MB Heap size: 2877.29MB +2024-07-01T10:00:40.958844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:00:41.307812Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:01:10.460899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:12.382720Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:12.716096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:12.839958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:13.099457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:13.564225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:14.474414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:15.240230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:15.421427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:15.623668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:15.671397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:15.771987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:16.239332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:16.279750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:16.354899Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:16.469549Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:16.746911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:17.797392Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:17.981401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:17.986867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:18.048111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:18.291103Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:18.414755Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:18.515540Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:21.451613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:23.304908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:24.071168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:38.432256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:40.388267Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:40.501635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:40.536718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:40.645702Z | Info | Live bytes: 833.18MB Heap size: 2877.29MB +2024-07-01T10:01:40.693074Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:40.732685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:40.958346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:41.068587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:41.148406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:41.677505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:44.730197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:45.089714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:45.152038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:45.258184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:45.290818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:45.341964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:45.590212Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:45.682163Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:45.807532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:46.399891Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:46.867571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:47.658008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:47.908280Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:47.965645Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:48.142307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:48.192652Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:48.252414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:01:48.434734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:48.512825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:01:48.899886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:02:22.189095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:02:22.298348Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:02:22.503377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:02:24.562039Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:02:24.622888Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:02:24.767617Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:02:24.874860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:02:29.906667Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:02:40.656734Z | Info | Live bytes: 876.26MB Heap size: 2877.29MB +2024-07-01T10:03:40.716921Z | Info | Live bytes: 878.63MB Heap size: 2877.29MB +2024-07-01T10:03:44.071212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:03:44.595979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:03:45.498949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:03:48.164880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:03:50.069646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:19.139035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:22.073614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:22.839901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:29.526118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:30.315803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:31.035396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:31.869539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:04:40.727807Z | Info | Live bytes: 908.91MB Heap size: 2877.29MB +2024-07-01T10:05:40.788586Z | Info | Live bytes: 921.45MB Heap size: 2877.29MB +2024-07-01T10:05:42.566063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:43.197846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:45.199989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:45.879283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:46.393911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:49.829405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:50.341605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:54.697064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:54.760734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:05:54.827051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:05:54.985160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:05:55.215248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:55.652794Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:05:55.762141Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:05:55.864151Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:05:55.976126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:55.992934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:05:56.563774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:05:57.079509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:04.017981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:04.632428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:05.194861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:05.933321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:06.654058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:07.248478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:07.763028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:08.339525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:09.016877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:09.571341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:10.880313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:19.033897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:29.217607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:30.141356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:34.434531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:35.174294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:06:40.796096Z | Info | Live bytes: 1000.82MB Heap size: 2877.29MB +2024-07-01T10:06:50.515070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:01.148534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:01.167958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:25.601340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:26.474100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:29.235430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:29.854538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:30.724264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:31.727661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:40.803827Z | Info | Live bytes: 1042.14MB Heap size: 2877.29MB +2024-07-01T10:07:43.015806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:44.119721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:45.057797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:45.808206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:47.330868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:07:48.201972Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:07:48.875423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:07.168219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:08.831887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:11.269210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:12.347963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:15.069725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:15.770561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:16.359957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:24.312459Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:24.447785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:24.552341Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:24.670833Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:24.758184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:25.363351Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:25.640521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:25.733283Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:25.796245Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:25.809708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:25.869840Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:26.338420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:28.758470Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:28.816936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:28.913533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:29.069709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:29.093334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:29.167069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:29.259043Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:29.357156Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:29.448423Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:29.557519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:29.634761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:32.382064Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:32.449901Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:32.593694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:32.660568Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:32.676989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:32.868582Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:32.976356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:33.330397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:37.097142Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:37.522869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:37.770779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:38.043209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:38.230131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:38.242239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:08:39.259216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:08:40.805843Z | Info | Live bytes: 1099.59MB Heap size: 2877.29MB +2024-07-01T10:08:47.694896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:09:22.069536Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:09:28.953805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:09:29.534680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:09:40.810111Z | Info | Live bytes: 1098.30MB Heap size: 2877.29MB +2024-07-01T10:10:01.092098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:08.614621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:08.738145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:08.858447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:08.947966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:09.071925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:09.082045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:09.220552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:09.693415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:10.440178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:25.603857Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:25.694292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:25.906594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:26.019516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:26.031729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:26.253376Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:26.462080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:26.692109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:10:26.720314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:27.394037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:30.096354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:30.719991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:31.246269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:10:40.820784Z | Info | Live bytes: 1114.34MB Heap size: 2877.29MB +2024-07-01T10:11:02.220020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:11:02.777400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:11:03.588194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:11:04.188403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:11:04.789153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:11:04.886920Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:11:40.857715Z | Info | Live bytes: 1140.09MB Heap size: 2877.29MB +2024-07-01T10:12:40.030755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:12:40.859922Z | Info | Live bytes: 1156.41MB Heap size: 2877.29MB +2024-07-01T10:12:42.568991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:12:43.026161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:12:44.066115Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:13:17.519834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:23.217214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:23.466625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:23.502579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:24.031185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:24.498836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:24.969839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:25.129962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:25.276621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:25.283640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:25.484717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:25.565853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:25.940283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:25.986952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:26.067583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:26.181483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:26.308155Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:13:26.451069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:27.236091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:28.243901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:28.929185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:29.624501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:30.784072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:31.341717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:13:31.943106Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:13:40.869646Z | Info | Live bytes: 1167.24MB Heap size: 2877.29MB +2024-07-01T10:14:01.380149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:01.387914Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:14:01.521128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:14:01.593735Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:14:01.970987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:02.536582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:06.392378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:06.422846Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:14:06.544569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:14:06.588189Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:14:07.009012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:08.020496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:08.583745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:16.412403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:16.946811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:17.514424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:14:17.971994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:18.369138Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:14:40.881667Z | Info | Live bytes: 1214.25MB Heap size: 2918.19MB +2024-07-01T10:14:49.336828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:52.267682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:14:53.041861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:07.163807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:08.028113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:09.335288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:10.193419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:15.657584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:15.793026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:15.856806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:15.932724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:15.979617Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:16.065677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:16.175262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:16.405152Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:16.449782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:16.754399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:17.025022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:17.084955Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:17.212901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:17.324551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:17.397169Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:17.644819Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:17.763735Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:17.793203Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:18.204859Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:15:18.672805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:21.596296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:22.071981Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:15:27.762416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:28.468613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:15:29.341856Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:15:40.893902Z | Info | Live bytes: 1256.66MB Heap size: 2984.25MB +2024-07-01T10:16:40.931063Z | Info | Live bytes: 1256.66MB Heap size: 2984.25MB +2024-07-01T10:17:16.261639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:16.306520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:16.383904Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:16.704876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:16.884270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:17.123535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:17.238960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:17.349252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:18.307359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:18.900781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:22.211015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:24.330114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:24.763551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:24.876625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:25.343743Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:17:40.947854Z | Info | Live bytes: 1276.44MB Heap size: 2984.25MB +2024-07-01T10:17:42.152956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:42.718152Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:42.884512Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:42.886317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:43.339128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:43.621023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:43.730527Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:43.796423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:43.861054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:44.321169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:48.527830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:48.894437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:48.953322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:49.135904Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:49.198621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:49.354329Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:49.409005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:49.524842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:17:49.875779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:17:51.247366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:00.469494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:02.360973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:02.449970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:02.606229Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:02.674383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:02.822343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:02.889206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:02.992397Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:03.357099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:04.069317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:04.532681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:11.372241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:11.540140Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:11.656165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:11.728698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:11.798964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:11.820694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:12.701505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:12.899573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:12.905025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:12.991856Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:13.243827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:13.399438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:13.431695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:13.971490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:14.752000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:21.682620Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:23.923985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:24.460369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:24.889882Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:24.957318Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:25.043435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:25.128130Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:25.208509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:25.427271Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:25.560882Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:25.596757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:25.699955Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:26.176427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:26.898829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:26.939736Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:26.994653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:27.149512Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:27.193844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:27.395292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:27.460635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:27.494723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:18:40.962451Z | Info | Live bytes: 662.46MB Heap size: 3010.46MB +2024-07-01T10:18:46.745566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:47.430116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:18:54.775438Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:19:41.009781Z | Info | Live bytes: 659.99MB Heap size: 3010.46MB +2024-07-01T10:20:41.031209Z | Info | Live bytes: 659.99MB Heap size: 3010.46MB +2024-07-01T10:21:02.415571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:21:13.036098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:21:13.652862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:21:41.058857Z | Info | Live bytes: 678.69MB Heap size: 3010.46MB +2024-07-01T10:22:41.118821Z | Info | Live bytes: 678.69MB Heap size: 3010.46MB +2024-07-01T10:23:08.994359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:23:41.150881Z | Info | Live bytes: 667.53MB Heap size: 3010.46MB +2024-07-01T10:24:41.199595Z | Info | Live bytes: 667.53MB Heap size: 3010.46MB +2024-07-01T10:25:36.177779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:41.259832Z | Info | Live bytes: 667.53MB Heap size: 3010.46MB +2024-07-01T10:25:47.428434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:47.977650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:51.902230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:52.505717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:54.893813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:55.606723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:56.116538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:56.683505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:58.177807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:25:58.763298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:00.903398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:01.574489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:02.209117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:03.258321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:03.800976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:04.326826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:04.975682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:05.632537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:06.210326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:06.764469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:07.302460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:07.909101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:08.611760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:09.132327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:09.637429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:10.380915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:11.016062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:12.276008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:12.920743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:13.977743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:14.738722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:15.360703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:16.952217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:17.727752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:18.330388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:18.845218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:19.748203Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:20.395128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:21.412829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:21.951436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:22.485584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:34.815076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:35.350594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:26:41.265924Z | Info | Live bytes: 752.20MB Heap size: 3010.46MB +2024-07-01T10:27:40.757691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:41.267664Z | Info | Live bytes: 759.97MB Heap size: 3010.46MB +2024-07-01T10:27:41.611127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:43.773059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:44.478505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:45.552917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:46.075882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:57.635826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:58.311644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:58.856993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:59.397306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:27:59.969119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:00.493157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:02.704989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:04.217871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:04.742522Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:05.253567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:05.784923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:06.404749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:06.919408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:07.509210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:08.075951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:08.652234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:09.303043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:09.951927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:10.563653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:11.312612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:11.871872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:12.414701Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:14.021895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:14.738792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:15.284337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:15.904481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:16.654711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:17.216392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:17.850569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:22.755470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:25.436076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:26.030407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:26.977640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:27.687328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:28.799699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:29.916796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:30.435125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:30.947347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:31.591086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:32.099864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:32.909878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:33.505056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:34.940526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:35.469208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:36.431914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:37.164132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:37.740532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:38.174069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:28:38.359470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:41.271979Z | Info | Live bytes: 857.61MB Heap size: 3010.46MB +2024-07-01T10:28:54.634939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:55.209925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:55.772629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:57.165316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:28:58.138578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:04.591491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:05.287871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:07.230823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:08.884077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:09.474262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:10.374083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:10.907082Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:11.499564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:12.085714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:12.702727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:13.731290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:14.341622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:14.852883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:15.463503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:16.324077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:17.663184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:18.555014Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:19.213953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:19.845210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:20.522487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:21.070291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:21.647502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:22.194062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:23.105413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:23.355916Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:29:23.710523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:24.216273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:25.451908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:26.248674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:26.788415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:27.405191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:29:27.874716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:28.868655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:29.538758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:30.147927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:31.217460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:35.880435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:37.503739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:39.086388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:39.614853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:40.220094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:40.808033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:41.273093Z | Info | Live bytes: 1123.13MB Heap size: 3010.46MB +2024-07-01T10:29:41.644387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:42.298447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:42.819909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:43.407425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:45.801256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:46.380238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:47.350416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:47.943983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:48.521483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:52.204092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:52.713173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:53.228556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:55.407150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:55.964924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:57.088138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:57.658447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:58.178217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:29:58.835711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:00.162956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:00.743806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:01.289648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:02.069905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:03.037494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:03.803289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:04.947774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:05.867962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:06.402568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:07.316865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:07.999071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:08.575771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:09.492075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:10.048028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:10.691759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:11.221020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:11.874668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:12.474964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:15.020770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:15.582733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:16.756810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:17.294668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:17.871932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:18.561353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:18.633482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:30:19.101330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:19.836478Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:30:20.519021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:21.810426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:22.201163Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:30:22.331584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:22.884687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:41.292905Z | Info | Live bytes: 1199.14MB Heap size: 3024.09MB +2024-07-01T10:30:48.414892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:50.083085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:50.927959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:54.246511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:30:54.295074Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:31:08.147122Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:08.941289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:09.453675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:10.325561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:10.843767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:11.400155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:11.605882Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:31:12.079355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:13.002875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:13.684709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:14.668023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:15.338756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:20.337922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:29.562530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:31.684206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:32.747646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:33.444247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:38.459248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:39.058835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:39.858318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:40.458783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:41.206674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:41.294681Z | Info | Live bytes: 1258.83MB Heap size: 3104.83MB +2024-07-01T10:31:42.058525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:45.521521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:46.132131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:46.708032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:47.312325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:47.830741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:48.350622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:48.912441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:31:49.419890Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:31:49.454730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:32:07.804640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:32:10.961365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:32:38.214675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:32:41.298754Z | Info | Live bytes: 1283.73MB Heap size: 3166.70MB +2024-07-01T10:32:53.431478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:32:54.521113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:32:58.778122Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:01.033069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:02.049971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:03.487622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:07.531328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:07.655980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:07.985808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:08.285262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:08.444054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:08.652707Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:08.842456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:09.109607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:09.286989Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:09.747291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:10.278463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:10.836164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:11.009559Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:11.206854Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:11.467644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:11.943109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:12.193013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:12.395724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:12.892390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:13.310247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:13.344744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:13.443850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:13.908957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:13.946521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T10:33:15.093692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:19.786964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:22.046840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:22.070677Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:33:22.750596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:24.590671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:26.473618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:27.132478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:27.672788Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T10:33:28.225361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T10:33:41.312763Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T10:34:41.321151Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:30:43.527408Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:31:43.531260Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:32:43.592372Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:33:43.653431Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:34:43.714221Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:35:43.775187Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:36:43.827572Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:37:43.856089Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:38:43.916193Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:39:43.971623Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:40:44.032410Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:41:44.093312Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:42:44.147514Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:43:44.208947Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:44:44.231013Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:45:44.292358Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:46:44.353464Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:47:44.414281Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:48:44.459487Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:49:44.520564Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:50:44.579571Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:51:44.595352Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:52:44.606418Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:53:44.667153Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:54:44.727877Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:55:44.789113Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:56:44.849416Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:57:44.910434Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:58:44.971755Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T11:59:45.032885Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:00:45.093532Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:01:45.154175Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:02:45.171342Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:03:45.232084Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:04:45.293139Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:05:45.353138Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:06:45.413840Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:07:45.474981Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:51:34.724901Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:52:34.785447Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:53:34.846104Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:54:34.859991Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:55:34.921251Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:56:34.982287Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:57:35.043535Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:58:35.104608Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T12:59:35.165231Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:00:35.226385Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:01:35.287708Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:02:35.348836Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:03:35.410388Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:04:35.471518Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:05:35.532311Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:06:35.593629Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:07:35.617221Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:08:35.678261Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:09:35.739552Z | Info | Live bytes: 709.40MB Heap size: 3166.70MB +2024-07-01T13:09:53.508391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:09:54.016630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:09:54.531301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:09:55.104378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:09:55.627359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:09:55.731796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:09:56.203344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:09:56.883856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:10:35.779120Z | Info | Live bytes: 736.04MB Heap size: 3166.70MB +2024-07-01T13:11:35.839598Z | Info | Live bytes: 736.04MB Heap size: 3166.70MB +2024-07-01T13:11:47.243232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:51.360665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:52.247704Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T13:11:52.795759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:55.746742Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:11:55.917179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:56.183772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:11:56.326045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:11:56.517655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:11:56.640365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:57.740197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:58.305634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:58.388590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:11:58.510905Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:11:58.586887Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:11:58.845190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:11:59.544449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:12:11.108290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:12:35.865815Z | Info | Live bytes: 756.87MB Heap size: 3166.70MB +2024-07-01T13:13:05.423776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:13:07.782509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:13:09.287195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:13:15.172522Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:13:16.170201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:13:35.886813Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:14:35.946675Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:15:35.996666Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:16:36.057891Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:17:36.119194Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:18:36.149974Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:19:36.206123Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:20:36.267384Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:21:36.285960Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:22:36.347315Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:23:36.374850Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:24:36.397945Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:25:36.458773Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:26:36.519840Z | Info | Live bytes: 776.08MB Heap size: 3166.70MB +2024-07-01T13:27:22.109098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:32.934244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:36.524954Z | Info | Live bytes: 771.86MB Heap size: 3166.70MB +2024-07-01T13:27:45.182731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:46.712109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:47.375983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:47.979071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:49.079477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:49.641761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:50.889089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:51.425823Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" ] +2024-07-01T13:27:51.566690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:54.275203Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:57.466873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:27:57.580879Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T13:28:01.222434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:04.903932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:06.213849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:08.028337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:09.494512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:09.753612Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" ] +2024-07-01T13:28:11.299839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:14.507999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:15.041021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:15.848567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:16.617692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:20.219076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:22.299020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:23.190452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:23.213158Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" ] +2024-07-01T13:28:24.145499Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ ] +2024-07-01T13:28:24.637496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:26.169892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:26.606782Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" ] +2024-07-01T13:28:28.288254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:30.555544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:31.688195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:33.170674Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T13:28:34.799545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:35.552471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:36.527734Z | Info | Live bytes: 869.47MB Heap size: 3185.57MB +2024-07-01T13:28:36.736659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:38.876068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:28:39.136815Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" ] +2024-07-01T13:29:15.411355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:19.271066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:24.828856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:25.146117Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T13:29:34.681206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:36.529453Z | Info | Live bytes: 1018.25MB Heap size: 3187.67MB +2024-07-01T13:29:38.790741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:42.527516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:45.393755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:47.458227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:50.113764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:51.841495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:52.726038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:55.281282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:58.252931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:29:59.735813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:30:02.569155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:30:03.731858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:30:05.410265Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T13:30:05.959810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:30:34.667111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:30:36.531717Z | Info | Live bytes: 1390.98MB Heap size: 3187.67MB +2024-07-01T13:30:39.935008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:30:43.742811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:36.307325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:36.585517Z | Info | Live bytes: 702.49MB Heap size: 3187.67MB +2024-07-01T13:31:38.879422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:39.901871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:40.423720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:40.940882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:41.454987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:41.971585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:42.549035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:43.239243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:49.872314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:31:59.255005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:00.577626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:08.555864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:12.943869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:12.947466Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T13:32:13.513854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:33.656491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:34.170894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:36.587708Z | Info | Live bytes: 882.57MB Heap size: 3187.67MB +2024-07-01T13:32:37.730500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:32:41.267067Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T13:33:36.643553Z | Info | Live bytes: 882.57MB Heap size: 3187.67MB +2024-07-01T13:33:41.621098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:33:46.241753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:33:50.684447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:33:50.790006Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:33:50.868201Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:33:51.048481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:33:51.095723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:33:51.247920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:33:51.307431Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:33:51.871133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:33:51.965960Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T13:33:52.641288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:34:27.599039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:34:36.649119Z | Info | Live bytes: 980.26MB Heap size: 3187.67MB +2024-07-01T13:35:36.709766Z | Info | Live bytes: 980.26MB Heap size: 3187.67MB +2024-07-01T13:36:36.770570Z | Info | Live bytes: 994.64MB Heap size: 3187.67MB +2024-07-01T13:36:53.436245Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:06.119670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:18.369579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:18.911513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:19.571974Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:37:19.717900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:37:19.814450Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T13:37:20.008704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:25.918701Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:36.780797Z | Info | Live bytes: 1004.30MB Heap size: 3187.67MB +2024-07-01T13:37:48.188390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:49.617243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:49.645535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:37:53.205401Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T13:37:53.268338Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T13:37:53.300105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T13:38:36.815717Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:39:36.876580Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:40:36.930678Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:41:36.990560Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:42:37.019117Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:43:37.054337Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:44:37.114600Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:45:37.174524Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:46:37.210030Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:47:37.232725Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:48:37.243550Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:49:37.303792Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:50:37.364601Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:51:37.425483Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:52:37.485619Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:53:37.546555Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:54:37.606616Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T13:55:37.667656Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T14:15:42.190161Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T14:16:42.250284Z | Info | Live bytes: 1035.59MB Heap size: 3187.67MB +2024-07-01T14:17:08.916250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:09.519554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:16.671740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:18.425052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:18.634987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:18.786247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:18.877859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:19.243670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:19.479569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:19.541017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:19.651033Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:19.706065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:19.709602Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:20.295079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:20.482987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:20.529027Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:20.797871Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:20.885120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:20.899763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:20.946531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:21.407663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:21.413367Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:21.685895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:21.770475Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:21.849322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:22.107562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:25.889662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:31.814439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:32.424806Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:17:40.422188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:41.651131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:42.251980Z | Info | Live bytes: 1051.53MB Heap size: 3187.67MB +2024-07-01T14:17:42.327137Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:17:59.076544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:59.199238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:17:59.254617Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:59.335304Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:59.447210Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:59.503618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:59.581428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:17:59.727132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:00.602257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:00.802984Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:18:10.400305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:11.242728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:11.987653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:12.368386Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:18:27.169390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:27.332815Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:18:27.510841Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:18:27.999694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:42.266693Z | Info | Live bytes: 1216.84MB Heap size: 3187.67MB +2024-07-01T14:18:50.781561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:51.373316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:54.074776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:54.693136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:18:54.877528Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:19:01.914641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:19:09.414987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:19:11.920971Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:19:11.970502Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:19:12.139295Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:19:12.211346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:19:12.275492Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:19:12.309564Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:19:12.369292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:19:12.896718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:19:12.990056Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T14:19:15.114700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:19:15.386168Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:19:15.573895Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:19:15.850498Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:19:15.850502Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:19:16.063041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:19:42.283569Z | Info | Live bytes: 742.45MB Heap size: 3187.67MB +2024-07-01T14:20:42.339843Z | Info | Live bytes: 742.45MB Heap size: 3187.67MB +2024-07-01T14:21:42.359473Z | Info | Live bytes: 742.45MB Heap size: 3187.67MB +2024-07-01T14:22:42.371429Z | Info | Live bytes: 742.45MB Heap size: 3187.67MB +2024-07-01T14:23:42.431495Z | Info | Live bytes: 742.45MB Heap size: 3187.67MB +2024-07-01T14:23:47.858046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:23:48.840883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:42.480311Z | Info | Live bytes: 825.21MB Heap size: 3187.67MB +2024-07-01T14:24:42.889131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:43.455791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:44.029839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:51.611844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:24:51.853256Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:24:52.066334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:52.081421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:24:52.186827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:24:52.694832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:54.498513Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:24:54.954051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:55.983803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:24:57.959063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:25:07.772469Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:25:07.988181Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:25:08.041088Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:25:08.122049Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:25:08.226486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:25:08.747264Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:25:42.350606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:25:42.481586Z | Info | Live bytes: 890.77MB Heap size: 3187.67MB +2024-07-01T14:25:43.452171Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:25:43.602177Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:25:43.635108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:08.876484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:09.493114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:10.046341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:11.363593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:11.875013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:12.341519Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:26:12.519270Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:26:13.015870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:18.204196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:18.402817Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:18.485787Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:18.544988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:18.640838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:24.431864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:24.504851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:24.628959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:24.673507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:24.688839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:24.758112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:24.799529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.065705Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.174688Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.223926Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.237472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:25.294936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.395932Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.606144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.742215Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:25.785474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:25.894683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:26:26.388299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:26.407530Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:26:26.591414Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:26:27.078607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:26:42.493787Z | Info | Live bytes: 1223.94MB Heap size: 3187.67MB +2024-07-01T14:27:05.344608Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:27:05.409870Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:27:05.506921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:20.706810Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:27:20.760684Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:27:20.795586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:38.123023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:38.753657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:39.604303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:39.917099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:39.995709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:40.176695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:40.220423Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:40.287517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:40.360417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:40.382808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:40.813005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:40.919393Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:40.923853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.124640Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.162442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.209926Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.259613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.465977Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.618497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:41.773427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.877431Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:41.993517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:42.264230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:42.329716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:42.474942Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:42.495495Z | Info | Live bytes: 1421.20MB Heap size: 3187.67MB +2024-07-01T14:27:42.822750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:43.016657Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:43.209848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:43.496957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:43.627368Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:44.115059Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:44.115324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:44.393734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:44.542848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:44.774008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:44.883449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:45.058018Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:45.207861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:45.314842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:45.550038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:45.878688Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:27:46.069655Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:27:46.097497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:53.429304Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:53.474731Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:53.629054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:53.637629Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:53.687482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:53.791356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:54.159723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:54.293749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:54.393638Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:54.561852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:54.774942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:55.337305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:55.731439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:55.849735Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:55.922048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:55.967471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:56.045131Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:56.307029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:56.385992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:56.450967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:56.512562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:56.523256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:56.631783Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:57.127038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:57.219568Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:57.516322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:57.714264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:57.716596Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:57.812935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:58.301194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:27:59.407788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:59.580883Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:27:59.901133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:00.276950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:00.438828Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:02.736078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:03.215019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:03.459679Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:03.708602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:04.442365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:04.728424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:04.965779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:05.023108Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:05.493432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:05.583520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:05.796387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:06.073804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:06.249928Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:28:06.401867Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:28:06.888794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:19.336844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:19.399468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:19.538532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:19.610447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:19.696919Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:19.734790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:19.788067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:20.143855Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:20.262722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:20.309767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:20.430450Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:20.713800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:20.884197Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:20.923173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:20.978177Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:21.031281Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:28:21.379933Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:28:21.466618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:21.553563Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:28:22.049298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:41.753266Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:28:41.815947Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:28:41.912439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:28:42.496833Z | Info | Live bytes: 1136.81MB Heap size: 3187.67MB +2024-07-01T14:29:42.544406Z | Info | Live bytes: 1133.34MB Heap size: 3187.67MB +2024-07-01T14:30:42.605406Z | Info | Live bytes: 1133.34MB Heap size: 3187.67MB +2024-07-01T14:31:42.653151Z | Info | Live bytes: 1133.34MB Heap size: 3187.67MB +2024-07-01T14:31:48.961261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:02.640544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:27.523389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:27.699340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:27.776745Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:27.847121Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:27.924011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:28.479785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:28.603557Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:28.658511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:28.760704Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:28.865438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:28.993046Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:29.082607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:29.185853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:29.234314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:29.750741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:29.828286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:30.170079Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:30.313070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:30.320801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:30.386109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:32:30.875380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:31.087130Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T14:32:31.761732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:42.656243Z | Info | Live bytes: 1241.70MB Heap size: 3187.67MB +2024-07-01T14:32:47.833429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:51.880716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:52.131105Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:32:52.321034Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:32:52.403926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:56.861880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:32:56.964320Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:32:57.148578Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:32:57.638678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:33:03.261416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:33:03.938734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:33:14.965187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:33:15.919488Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:33:16.476367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:33:39.848221Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:33:39.915312Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:33:39.965973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:33:42.658529Z | Info | Live bytes: 841.29MB Heap size: 3187.67MB +2024-07-01T14:33:50.568455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:34:03.721890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:34:04.388119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:34:36.982476Z | Info | LSP: received shutdown +2024-07-01T14:34:36.984254Z | Error | Got EOF +2024-07-01T14:34:46.200333Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-01T14:34:46.201209Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01T14:34:46.201485Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T14:34:46.204319Z | Info | Logging heap statistics every 60.00s +2024-07-01T14:34:46.214946Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T14:34:46.215467Z | Info | Starting server +2024-07-01T14:34:46.217119Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-01T14:34:46.248025Z | Info | Started LSP server in 0.03s +2024-07-01T14:34:47.735106Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs +2024-07-01T14:34:47.736098Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T14:34:48.227548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:34:48.227578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:34:49.219586Z | Info | Load cabal cradle using single file +2024-07-01T14:34:50.173828Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT300949-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-01T14:34:53.471780Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-57be9437b2c911e2f75d7c43930aaaa83fcf6215 +2024-07-01T14:34:53.478236Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-01T14:35:46.219523Z | Info | Live bytes: 568.95MB Heap size: 1758.46MB +2024-07-01T14:36:04.854373Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:04.967854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:05.012973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:05.092274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:05.177923Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:05.226253Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:05.489776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:05.896689Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:06.007852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:06.105227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:06.182428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:06.603020Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:06.660630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:06.901634Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:06.996635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:07.095433Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:07.170675Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:07.322725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:07.376194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:08.178143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:08.519365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:08.864035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:08.920293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:09.050636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:09.130040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:36:09.403727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:09.503913Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T14:36:10.178396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:34.442894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:36:46.222561Z | Info | Live bytes: 640.82MB Heap size: 2172.65MB +2024-07-01T14:37:09.946439Z | Info | LSP: received shutdown +2024-07-01T14:37:09.947664Z | Error | Got EOF +2024-07-01T14:37:09.947834Z | Info | Reactor thread stopped +2024-07-01T14:37:22.620452Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-01T14:37:22.621478Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-01T14:37:22.621721Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T14:37:22.624041Z | Info | Logging heap statistics every 60.00s +2024-07-01T14:37:22.633225Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-01T14:37:22.633941Z | Info | Starting server +2024-07-01T14:37:22.635818Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-01T14:37:22.676727Z | Info | Started LSP server in 0.04s +2024-07-01T14:37:24.051827Z | Info | Cradle path: cardano-api/internal/Cardano/Api/IPC.hs +2024-07-01T14:37:24.052937Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-01T14:37:24.567761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:37:24.568027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:37:25.532643Z | Info | Load cabal cradle using single file +2024-07-01T14:37:26.489691Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT304495-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-01T14:37:28.181957Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" +2024-07-01T14:37:28.247087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:37:33.305425Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-648e747809904bf8a445e4ab5be3a6d6f62ad1c0 +2024-07-01T14:37:33.311777Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-01T14:38:22.661455Z | Info | Live bytes: 729.42MB Heap size: 1929.38MB +2024-07-01T14:38:43.409461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:38:44.546448Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:38:44.744252Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:38:44.804654Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:38:45.028805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:38:45.260733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:38:45.388467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:38:45.456998Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:38:45.580680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:38:45.753633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:38:46.348601Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:38:46.416201Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:38:46.432976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:38:54.367261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:38:57.566076Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:39:14.514944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:15.572472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:15.757554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:15.823423Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:15.931943Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:15.974723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:15.987045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:16.547601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:17.072461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:17.189324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:17.245302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:17.367627Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:17.439083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:17.817401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:17.840541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:18.401371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:18.531737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:18.619397Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:18.762247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:18.913930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:19.570890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:19.620355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:19.836670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:19.963507Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:20.053904Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:20.158950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:20.620852Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:39:20.820445Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:39:21.293694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:22.663218Z | Info | Live bytes: 858.19MB Heap size: 2457.86MB +2024-07-01T14:39:44.311925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:45.485851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:46.761263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:47.804028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:48.790156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:49.126886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:39:49.543037Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:39:49.611516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:39:49.760125Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:39:50.249674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:01.568822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:02.335275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:02.504235Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:02.587446Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:02.644931Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:02.704394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:02.705592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:03.195450Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:03.272586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:03.301036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:03.480914Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:03.774168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:03.846142Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:03.914705Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:03.951017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:04.053021Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:04.407337Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:04.495654Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:04.528439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:04.532649Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:05.179147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:05.393921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:05.547193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:05.642918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:05.672527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:05.836259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:05.850723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:06.090107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:06.187619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:06.341227Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:06.341226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:06.425710Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:06.514261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:06.671181Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:06.922222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:06.966251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:07.306340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:07.405029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:40:07.440831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:07.704344Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:40:07.893932Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:40:08.384174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:22.674373Z | Info | Live bytes: 1219.03MB Heap size: 2457.86MB +2024-07-01T14:40:43.150023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:43.912321Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:40:43.951514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:40:43.992252Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:40:44.479608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:41:17.355875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:41:17.506393Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:41:22.679501Z | Info | Live bytes: 734.47MB Heap size: 2882.54MB +2024-07-01T14:41:39.764089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:41:40.074440Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ ] +2024-07-01T14:41:40.283847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:41:41.379819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:41:41.888384Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:41:41.995349Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:41:42.479006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:42:22.682520Z | Info | Live bytes: 902.48MB Heap size: 2882.54MB +2024-07-01T14:42:34.764544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:42:35.342967Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:42:35.410649Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:42:35.595426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:42:53.787491Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:42:53.826493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:14.656488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:15.562697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:17.846249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:19.138699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:19.904307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:20.658845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:21.183051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:21.549369Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:43:21.735696Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:43:22.220596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:22.684332Z | Info | Live bytes: 1158.10MB Heap size: 2882.54MB +2024-07-01T14:43:27.661779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:28.712008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:30.248623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:36.579802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:38.922331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:40.888159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:43:43.864734Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:43:43.917605Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:43:44.414912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:44:22.723256Z | Info | Live bytes: 737.02MB Heap size: 2904.56MB +2024-07-01T14:44:28.117530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:44:33.964747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:44:34.064045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:44:34.160024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:44:34.214623Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:44:34.683052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:44:35.025289Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:45:14.324998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:45:22.729267Z | Info | Live bytes: 780.74MB Heap size: 2904.56MB +2024-07-01T14:45:58.009305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:46:22.754447Z | Info | Live bytes: 790.24MB Heap size: 2904.56MB +2024-07-01T14:46:41.864356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:46:43.558656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:46:51.202852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:22.787548Z | Info | Live bytes: 806.69MB Heap size: 2904.56MB +2024-07-01T14:47:30.763685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:31.645236Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:47:34.996296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:39.238412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:39.564243Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC/Monad.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-01T14:47:39.770940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:45.150132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:46.122623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:48.048933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:49.108558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:51.955697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:52.585992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:54.404622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:55.584081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:58.256587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:47:59.404953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:48:00.101855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:48:03.617937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:48:05.396685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:48:08.118841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:48:09.089574Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:48:22.790453Z | Info | Live bytes: 702.26MB Heap size: 2976.91MB +2024-07-01T14:49:22.800180Z | Info | Live bytes: 702.26MB Heap size: 2976.91MB +2024-07-01T14:50:22.803239Z | Info | Live bytes: 702.26MB Heap size: 2976.91MB +2024-07-01T14:51:22.813893Z | Info | Live bytes: 702.26MB Heap size: 2976.91MB +2024-07-01T14:52:19.726402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:52:22.818075Z | Info | Live bytes: 730.07MB Heap size: 2976.91MB +2024-07-01T14:52:39.634995Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/IPC/Generic.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" ] +2024-07-01T14:52:53.801388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:52:56.526215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:08.431421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:10.846256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:12.857752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:21.332909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:22.822157Z | Info | Live bytes: 715.48MB Heap size: 2976.91MB +2024-07-01T14:53:35.723179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:36.217808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:53:36.357362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:53:36.403190Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:53:36.483649Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:53:36.529862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:53:36.556793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:37.097137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:37.155699Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ ] +2024-07-01T14:53:37.792886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:43.940601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:46.224815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:46.957415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:47.000570Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-01T14:53:49.099767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:53:52.515747Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T14:54:22.835559Z | Info | Live bytes: 978.74MB Heap size: 2976.91MB +2024-07-01T14:55:22.896696Z | Info | Live bytes: 978.74MB Heap size: 2976.91MB +2024-07-01T14:55:49.918273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:50.504252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:51.242766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:51.869136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:52.443768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:52.829261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:55:52.898693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:55:52.988446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:53.513928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:54.046713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:54.185935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:55:54.241641Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:55:54.630390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:55.199283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:55:55.810892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:01.760838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:03.166180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:04.047625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:04.909365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:16.212832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:20.886075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:20.909227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:22.898479Z | Info | Live bytes: 1009.95MB Heap size: 2976.91MB +2024-07-01T14:56:45.142356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:46.050823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:46.306207Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:46.394011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:46.491166Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:46.716593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:46.773568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:46.840146Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:46.920542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:46.995328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:47.090527Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:47.161163Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:47.313822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:47.673980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:47.899905Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:48.045599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:48.104305Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:48.146772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:56:48.146943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:48.777069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:49.406158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:51.970240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:55.670302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:56.362420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:57.042882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:57.572214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:58.353321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:58.889842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:56:59.833959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:00.006704Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:00.469563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:01.045197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:06.473705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:09.819406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:12.270845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:12.321737Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T14:57:12.479666Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T14:57:12.977123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:22.908683Z | Info | Live bytes: 1087.43MB Heap size: 2976.91MB +2024-07-01T14:57:25.921672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:38.553142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:40.491533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:42.163007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:43.462382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:43.878363Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T14:57:44.548008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:49.249266Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:49.347690Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:49.422916Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:49.487738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:49.678257Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:49.701016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:49.747621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:49.895987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:49.999899Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:50.081011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:50.213394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:52.644981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:52.716312Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:53.013531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:53.256297Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:53.718829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:53.826625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:53.930234Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.002482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.082373Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.225713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.274487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:54.325505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.459040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.572647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.768215Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:54.789778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:55.277379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:55.402459Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:55.605277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:55.842576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:55.925134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:56.009274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:56.300342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:57.948685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.061767Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.123906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.238918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.353808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.408349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:58.452972Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.571392Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.674034Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.726485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.827063Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:57:58.917599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:57:59.478425Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T14:58:04.295089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:04.325907Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T14:58:04.886131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:22.924716Z | Info | Live bytes: 1182.86MB Heap size: 2976.91MB +2024-07-01T14:58:41.299893Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:41.350191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:41.544290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:41.608453Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:41.660010Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:41.695259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:41.733659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:42.269390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:42.412058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:42.556191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:42.749369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:42.818498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:42.861041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:42.994820Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:43.130105Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:43.241365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:43.337481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:44.132710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:44.362833Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:44.744681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:46.547229Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:46.718777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:46.739035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:46.832905Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:46.963428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:47.045986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:47.231950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:47.327538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:47.646654Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:47.794843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:47.929562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:47.976277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:48.135627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:48.162440Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:48.656231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:49.388941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:49.940149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:49.987197Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T14:58:50.650517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:53.750767Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:53.856714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:53.975234Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:54.059852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:54.137035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:54.291815Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:54.585426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:54.619897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:54.697869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:54.818369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:54.943888Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:54.980083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:58:55.158891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:58:55.504278Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T14:59:12.592055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:12.903224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:12.988961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:13.055266Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:13.318324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:13.326200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:13.446094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:13.520870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:13.622229Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:13.783112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:13.914541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:13.932034Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:14.278259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:14.328010Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:14.429560Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:14.746082Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:15.258069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:15.495898Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:15.529165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:15.602149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:15.682720Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:15.730534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:16.290155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:16.916602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:20.012505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:22.926157Z | Info | Live bytes: 714.52MB Heap size: 3009.41MB +2024-07-01T14:59:22.984174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:23.959628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:26.185161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:27.523583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:34.804649Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:35.263450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:35.825391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:36.496496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:40.216744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:41.057570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:41.901150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:42.253106Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:42.379614Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T14:59:42.430998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:43.008743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:46.812944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:47.873222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:48.310562Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T14:59:48.974687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:53.355208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:55.747419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T14:59:56.765052Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-01T14:59:56.802750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:01.516309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:04.811171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:11.386985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:11.999262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:12.061326Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:00:12.513444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:13.442353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:14.724350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:15.975110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:16.799718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:16.950713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:00:17.312141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:20.064014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:00:20.434515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:00:20.520420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:21.142538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:00:22.928240Z | Info | Live bytes: 755.56MB Heap size: 3009.41MB +2024-07-01T15:00:26.699767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:14.021656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:15.789992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:17.826184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:19.384346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:20.719473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:21.401255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:22.930434Z | Info | Live bytes: 784.47MB Heap size: 3009.41MB +2024-07-01T15:01:23.813067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:25.628076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:27.414651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:28.783867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:30.766156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:32.417049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:33.723713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:34.477727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:35.651181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:36.868440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:39.521320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:43.781084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:45.003595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:46.569712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:47.861141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:50.686370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:52.722182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:55.448624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:57.337673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:58.926188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:01:59.960214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:02.335461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:07.139246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:08.607325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:09.236205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:11.621731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:12.708364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:13.059570Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:02:13.166974Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:02:13.311827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:14.371286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:22.940197Z | Info | Live bytes: 821.19MB Heap size: 3009.41MB +2024-07-01T15:02:25.951412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:52.251308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:02:56.014876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:03.280750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:22.956380Z | Info | Live bytes: 823.84MB Heap size: 3009.41MB +2024-07-01T15:03:24.876898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:36.277832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:36.511185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:36.576505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:36.749004Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:36.807276Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:36.873440Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:36.935820Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:36.963817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:37.193472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:37.308716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:37.382569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:37.437022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:37.479428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:37.567625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:37.787421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:37.993424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:38.074191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:38.077195Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:39.054305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:39.779804Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:39.921393Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:40.027350Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:03:40.262165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:40.462424Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:03:40.635282Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:03:41.130388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:03:55.817656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:04:08.263691Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:04:08.323054Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:04:08.339010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:04:22.969586Z | Info | Live bytes: 983.70MB Heap size: 3009.41MB +2024-07-01T15:04:24.568794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:04:33.705712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:04:42.951066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:04:54.120691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:04:58.232552Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:04:58.295784Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:04:58.413713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:05:22.654276Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:05:22.732236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:05:22.883789Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:05:22.951667Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:05:22.970866Z | Info | Live bytes: 1110.74MB Heap size: 3009.41MB +2024-07-01T15:05:23.034423Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:05:23.076790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:05:23.106957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:05:23.645199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:05:24.184720Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:05:24.271953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:05:24.307698Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:05:24.800630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:05:33.974854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:05:46.195190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:05:55.552121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:06.278744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:08.255217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:08.436526Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:06:14.891296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:22.506471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:22.984610Z | Info | Live bytes: 1298.58MB Heap size: 3009.41MB +2024-07-01T15:06:28.598281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:29.544178Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:29.671581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:29.737715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:29.819348Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:30.002434Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:30.018480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:30.581303Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:06:30.828567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:40.905945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:41.623704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:50.139342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:50.191230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:50.361513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:50.378966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:50.511409Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:50.548536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:50.832722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:50.983603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:51.002484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:51.171849Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:51.352538Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:06:51.650381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:06:52.238410Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:01.007873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:01.879939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:01.995250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:02.071403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:02.204752Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:02.315294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:02.362626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:02.413615Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:02.522333Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:02.608107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:02.904032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:03.094123Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:07:03.274728Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:07:03.766271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:22.990245Z | Info | Live bytes: 1058.52MB Heap size: 3040.87MB +2024-07-01T15:07:30.189624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:30.468603Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:30.538183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:30.680539Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:30.747761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:30.821742Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:30.928204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:31.067936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:31.376501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:31.472486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:31.536716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:31.538982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:31.689396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:31.739189Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:31.774342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:31.824936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:32.012979Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:32.177317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:32.388989Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:32.554826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:32.672440Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:32.865269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:32.980105Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:33.307460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:33.462006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:33.537923Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:33.649848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:33.771269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:33.879017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:34.030289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:34.155898Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:34.253245Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:34.395233Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:34.454996Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:34.561896Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:34.650657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:34.738653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:34.857854Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:35.155768Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:07:35.234536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:35.385029Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:07:35.877279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:42.557814Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:42.655415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:42.715037Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:42.832261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:42.928148Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:42.999905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:43.125370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:43.448702Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:43.505154Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:43.575278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:43.617593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:43.683021Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:07:44.167556Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:07:44.183904Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:51.220278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:07:55.968028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:08:00.348155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:08:00.758002Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:08:00.855205Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:08:01.012655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:08:01.069006Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:08:01.164263Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:08:01.206478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:08:01.234178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:08:01.787187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:08:01.885199Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:08:02.065151Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:08:02.555935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:08:14.295043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:08:23.008184Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:09:23.019884Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:10:23.080818Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:11:23.141393Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:12:23.202204Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:13:23.263190Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:14:23.324145Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:15:23.384257Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:16:23.387418Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:17:23.448424Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:18:23.456005Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:19:23.468326Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:20:23.529624Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:21:23.587573Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:22:23.648728Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:23:23.661813Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:24:23.722896Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:25:23.783044Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:26:23.844239Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:27:23.889487Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:28:23.950592Z | Info | Live bytes: 805.30MB Heap size: 3170.89MB +2024-07-01T15:29:24.006750Z | Info | Live bytes: 810.51MB Heap size: 3170.89MB +2024-07-01T15:29:30.647722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:29:32.006330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:29:32.955124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:29:37.323890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:29:37.559307Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-01T15:29:52.663467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:23.042742Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:23.110907Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:23.249362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:23.283941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:23.308727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:23.423771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:23.776992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:23.861667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:23.911723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.007751Z | Info | Live bytes: 1383.53MB Heap size: 3170.89MB +2024-07-01T15:30:24.010932Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.148699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.312991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.385286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:24.436413Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.528588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.627426Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.772453Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:24.910974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:25.595304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:26.470766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:26.768202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:27.146810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:27.320379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:27.507235Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:27.632173Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:27.870670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:28.017573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.158748Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.272103Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.341529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.470873Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.511102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:28.622975Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.676382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.789952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.859109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:28.969342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:29.114213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:29.370421Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:30:29.550596Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:30:30.037668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:47.749895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:48.324688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:48.961534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:49.223366Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:49.477208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:49.713746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:49.991268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:50.289258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:50.746740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:51.074366Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:51.266156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:51.459268Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:51.605325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:51.715662Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:51.918192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:51.937857Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:52.020056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:52.118479Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:52.484394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:54.868070Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:54.995943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:55.005443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.222515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.263437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.404569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.434424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:59.474861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.543677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.808898Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.911289Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:30:59.942034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:30:59.976478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.120022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.189717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.234270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.284494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.462083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:00.487869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.740107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.868786Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.933818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:00.975374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:01.154430Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:01.369564Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:01.470206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:01.585652Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:01.637774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:03.029894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:03.930378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:04.761418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:05.317422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:06.716629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:06.747484Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ ] +2024-07-01T15:31:07.304822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:10.967503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:11.036524Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ ] +2024-07-01T15:31:15.372597Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:15.511664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:15.587243Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:31:15.823766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:16.235499Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:31:16.412885Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:31:16.904670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:24.013865Z | Info | Live bytes: 715.97MB Heap size: 3220.18MB +2024-07-01T15:31:43.803371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:31:46.194313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:32:02.676261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:32:04.595527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:32:24.034177Z | Info | Live bytes: 794.09MB Heap size: 3220.18MB +2024-07-01T15:33:09.071526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:33:13.159008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:13.262954Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:13.369749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:13.481164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:13.609730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:33:13.644801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:13.794955Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:13.911137Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:14.067632Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:14.205328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:14.246757Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:14.256661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:33:15.121198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:15.294318Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:15.445980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:15.583984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:33:15.662647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:15.848022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:15.949588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:16.033822Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:33:16.129327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:33:17.287587Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:33:24.040319Z | Info | Live bytes: 909.05MB Heap size: 3220.18MB +2024-07-01T15:33:51.112023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:34:24.073333Z | Info | Live bytes: 936.54MB Heap size: 3220.18MB +2024-07-01T15:35:24.133854Z | Info | Live bytes: 936.54MB Heap size: 3220.18MB +2024-07-01T15:36:24.194425Z | Info | Live bytes: 936.54MB Heap size: 3220.18MB +2024-07-01T15:36:55.720631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:36:56.247549Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:36:56.546134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:36:56.606233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:36:56.623246Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:36:56.731123Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:36:56.806661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:36:56.911653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:36:57.152294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:36:57.204568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:36:58.507763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:36:59.019297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:36:59.784111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:00.453660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:01.047682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:01.597787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:02.358339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:03.148898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:03.699728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:04.454389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:05.555987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:06.476578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:07.152111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:07.898760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:08.522494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:08.622175Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:37:09.093403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:09.143387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:37:09.604609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:09.905387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:37:10.222884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:10.935807Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:37:11.028605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:11.604689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:12.223610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:12.788261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:13.703581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:15.052418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:37:24.204712Z | Info | Live bytes: 1013.71MB Heap size: 3220.18MB +2024-07-01T15:38:16.220862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:16.392332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:16.499903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:16.660988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:16.676983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:16.805211Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:16.919152Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:17.042707Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:17.187260Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:17.267881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:17.289668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:17.385650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:17.887793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:18.455162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:18.628771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:20.293827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:20.833073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:24.206241Z | Info | Live bytes: 1021.72MB Heap size: 3220.18MB +2024-07-01T15:38:24.413346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:47.333343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:38:47.776027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:48.375367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:48.916215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:49.640601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:50.880073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:51.725467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:52.323241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:52.981894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:54.387598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:55.341796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:56.633993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:58.505645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:38:59.090079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:00.708375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:01.626938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:02.353477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:02.406002Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:02.518625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:05.863392Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:06.034212Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:06.082525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:07.068302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:07.243801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:07.286177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:07.585694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:07.826983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:08.892394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:09.116729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:09.297572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:09.399978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:09.582009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:10.082759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:10.229188Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:10.553642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:11.792584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:12.506540Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:12.809112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:13.050204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:13.423729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:13.646156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:14.330807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:15.213625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:15.898135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:16.538189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:17.085892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:18.939277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:19.961937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:20.169663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:20.261428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:20.408323Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:20.423667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:20.544502Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:20.708591Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:20.848597Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:20.951488Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:21.003305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:21.063966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:21.144462Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:21.516960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:22.031070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:22.780081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:24.141402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:24.207206Z | Info | Live bytes: 1237.05MB Heap size: 3220.18MB +2024-07-01T15:39:24.430236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:24.695349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:24.973467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:25.201029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:25.840898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:26.535269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:26.662180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:27.224642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:27.292542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:27.775048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:28.478139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:29.144815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:30.540999Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:30.686390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:30.732438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:30.740737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:31.100776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:31.241467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:31.576120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:32.162888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:32.687812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:33.262780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:33.816176Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:34.020515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:34.146209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:34.785440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:35.471027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:36.165980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:36.707812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:37.265905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:37.398706Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:37.445680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:39:37.850618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:38.407823Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:39:38.492915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:39:38.506454Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:39:39.003460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:40:24.210293Z | Info | Live bytes: 1309.31MB Heap size: 3220.18MB +2024-07-01T15:41:24.253424Z | Info | Live bytes: 1309.31MB Heap size: 3220.18MB +2024-07-01T15:42:24.259488Z | Info | Live bytes: 1309.31MB Heap size: 3220.18MB +2024-07-01T15:43:24.320302Z | Info | Live bytes: 1309.31MB Heap size: 3220.18MB +2024-07-01T15:43:29.084459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:43:31.083339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:43:34.640682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:43:36.161051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:24.346427Z | Info | Live bytes: 1362.22MB Heap size: 3220.18MB +2024-07-01T15:44:49.391497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:51.210849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:51.745490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:52.465965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:52.938765Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:44:53.026558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:53.051793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:44:53.138714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:44:53.640753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:54.171712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:44:54.184287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:55.282972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:56.030449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:56.542707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:57.155676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:58.062675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:44:59.497771Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:45:14.467453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:15.299293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:15.599529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:15.756135Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:15.849862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:16.056868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:16.094576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:16.242825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:16.350938Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:16.491750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:16.566414Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:16.669665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:16.700844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:16.768169Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:17.268595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:17.732526Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:17.846149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:18.818929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:20.101081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:21.884808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:22.337975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:22.571885Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:45:24.348227Z | Info | Live bytes: 905.85MB Heap size: 3220.18MB +2024-07-01T15:45:29.861901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:29.969618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:30.152502Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:30.250628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:30.413925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:30.555889Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:31.009007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:31.151230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:31.259002Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:31.607669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:31.968378Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:32.177647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:32.291239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:32.427730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:32.854450Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:32.942527Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:33.024736Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:33.310237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:34.040213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:34.547297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:35.276295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:35.884415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:35.928285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:36.124196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:36.455783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:45:36.825861Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:45:39.309910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:45:39.491632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:06.384527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:07.382691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:08.772876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:08.977807Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:46:09.311267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:13.316444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:24.352394Z | Info | Live bytes: 959.15MB Heap size: 3220.18MB +2024-07-01T15:46:37.134064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:38.130226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:53.058967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:53.619798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:54.208426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:54.882002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:55.414428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:46:58.623367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:00.216489Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Block.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" ] +2024-07-01T15:47:04.917839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:05.427726Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:23.300469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:23.885318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:24.354712Z | Info | Live bytes: 1065.21MB Heap size: 3220.18MB +2024-07-01T15:47:34.001666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:37.597516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:48.373528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:56.784970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:47:56.868118Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:47:56.975205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:57.011869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:47:57.088202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:47:57.158826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:47:57.210876Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:47:57.486839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:47:57.853799Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs": [ ] +2024-07-01T15:47:58.060292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:01.488606Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Block.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" ] +2024-07-01T15:48:01.631767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:04.786612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:05.371833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:05.921386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:07.057448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:09.018015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:11.652382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:12.286891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:19.251855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:24.360595Z | Info | Live bytes: 1125.54MB Heap size: 3220.18MB +2024-07-01T15:48:24.970368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:39.458174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:44.342010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:52.368384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:48:58.170580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:12.517380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:17.015152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:19.807984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:23.593138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:49:23.637824Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:49:23.789441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:49:23.808067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:23.860507Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:49:23.910688Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:49:23.957078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:49:24.328403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:24.361984Z | Info | Live bytes: 1155.26MB Heap size: 3220.18MB +2024-07-01T15:49:24.720885Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs": [ ] +2024-07-01T15:49:25.395419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:31.808037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:38.154203Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:47.454337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:50.007013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:50.693142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:51.276442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:51.820692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:52.356296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:55.544801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:56.926826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:49:57.405127Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Block.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" ] +2024-07-01T15:49:58.760813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:03.019841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:03.751582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:04.495938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:09.653130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:24.371610Z | Info | Live bytes: 1249.80MB Heap size: 3220.18MB +2024-07-01T15:50:24.940786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:28.798336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:29.274152Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:50:29.415483Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:50:29.898668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:35.939818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:36.923863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:40.758218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:41.404723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:42.222962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:42.812616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:43.559871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:44.109997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:44.708771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:48.075882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:50.519942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:51.064932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:51.748433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:52.937686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:50:58.666928Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:51:10.012579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:10.129898Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:51:15.191714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:15.629877Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:51:15.921795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:24.381288Z | Info | Live bytes: 1339.03MB Heap size: 3220.18MB +2024-07-01T15:51:26.497693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:27.102053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:27.631095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:28.170178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:32.818780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:35.109220Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:35.194314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:35.351968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:35.394267Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:35.572455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:35.732921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:35.832485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:35.860671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:36.356724Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:51:46.128960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:47.279066Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:47.392411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:47.465886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:47.579188Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:47.751039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:48.412411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:48.594882Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:51:48.893926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:51:49.099339Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:52:24.415768Z | Info | Live bytes: 838.82MB Heap size: 3278.90MB +2024-07-01T15:52:55.496558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:03.855495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:04.043999Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:04.061413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:04.239775Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:04.328590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:04.700970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:24.419840Z | Info | Live bytes: 909.21MB Heap size: 3278.90MB +2024-07-01T15:53:27.204796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:27.431525Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:27.634254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:28.056027Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:28.119550Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:28.213407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:28.312128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:28.441839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:28.519567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:28.567228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:28.900818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:28.991790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:29.030234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:29.098513Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:29.550042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:29.865162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:29.995324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:30.146400Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:30.319160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:30.801616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:30.945666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:31.060290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:31.180641Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:31.241293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:31.267355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:31.501081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:31.958489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:37.058326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:37.638366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:39.413017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:43.604428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:43.629422Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:43.695112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:43.777773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:44.011621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:44.043827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:44.942880Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:53:45.016232Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:53:45.122740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:52.033865Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:52.095124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:52.259291Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:52.267287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:52.321084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:52.488936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:52.578333Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:53:52.789881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:53:52.905459Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:54:24.452033Z | Info | Live bytes: 1185.80MB Heap size: 3278.90MB +2024-07-01T15:55:24.494152Z | Info | Live bytes: 1185.80MB Heap size: 3278.90MB +2024-07-01T15:55:29.893687Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:30.325682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:30.579680Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:55:53.551841Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:53.973815Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:54.021258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:54.073032Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:54.163160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:54.218968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:54.564242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:55.004078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:55.313631Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:55.481770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:55.494484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:55.565106Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:55.915086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:56.048589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:56.281171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:56.364906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:55:56.585791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:58.094917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:58.696423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:59.313204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:55:59.550632Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:55:59.718511Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:56:00.216703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:56:24.517659Z | Info | Live bytes: 1410.10MB Heap size: 3278.90MB +2024-07-01T15:56:51.628517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:56:52.207773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:57:09.953208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:57:13.469397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:57:15.280373Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:57:15.748345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:57:15.780350Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:57:16.009008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T15:57:16.359415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:57:20.344704Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T15:57:20.424875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T15:57:24.523026Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T15:58:24.583379Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T15:59:24.643223Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:00:24.703317Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:01:24.763259Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:02:24.823714Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:03:24.884242Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:04:24.944210Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:05:25.004723Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:06:25.006746Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:07:25.066385Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:08:25.126418Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:09:25.186471Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:10:25.235846Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:11:25.251310Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:12:25.311168Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:13:25.359596Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:14:25.420212Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:15:25.480579Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:16:25.494995Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:17:25.555251Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:18:25.615248Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:19:25.675302Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:20:25.735344Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:21:25.795431Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:22:25.855257Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:23:25.915194Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:24:25.942503Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:25:25.955585Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:26:26.016816Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:27:26.019568Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:28:26.080765Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:29:26.141391Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:30:26.198055Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:31:26.259423Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:32:26.282414Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:33:26.343683Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:34:26.404946Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:35:26.465500Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:36:26.478466Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:37:26.539396Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:38:26.584978Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:39:26.646038Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:40:26.707373Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:41:26.760385Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:42:26.821595Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:43:26.882412Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:44:26.907490Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:45:26.968371Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:46:27.005211Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:47:27.038833Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:48:27.040522Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:49:27.060914Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:50:27.121327Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:51:27.182164Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:52:27.227526Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:53:27.253285Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:54:27.307432Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:55:27.368182Z | Info | Live bytes: 1545.10MB Heap size: 3278.90MB +2024-07-01T16:55:37.183187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:37.405325Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T16:55:40.458101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:42.066717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:42.191265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:42.443540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:42.570463Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:42.660931Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:42.747978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:42.914881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:44.082009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:44.374962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:44.479219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:44.607273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:44.836998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:45.931993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:46.463421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:48.072718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:48.708717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:50.341771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:50.938569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:51.016347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:51.556663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:51.906262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:55:52.087163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:53.504700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:54.067844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:55.025407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:55:56.161041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:56:27.394202Z | Info | Live bytes: 1606.35MB Heap size: 3278.90MB +2024-07-01T16:57:27.400156Z | Info | Live bytes: 1606.35MB Heap size: 3278.90MB +2024-07-01T16:58:27.460385Z | Info | Live bytes: 1606.35MB Heap size: 3278.90MB +2024-07-01T16:58:33.474435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:59:05.095544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:59:27.463262Z | Info | Live bytes: 779.91MB Heap size: 3391.09MB +2024-07-01T16:59:56.039269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:59:56.300273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:59:56.310424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:59:56.813960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:59:56.942165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:59:57.013851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:59:57.471605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:59:57.481994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:59:57.585883Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:59:58.053651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:59:58.614404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T16:59:59.631619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T16:59:59.842476Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:00.061524Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:00.086871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:00.158644Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:00.627643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:01.202982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:01.717446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:03.015420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:03.570448Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:03.619484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:04.340416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:05.135532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:05.654321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:06.687303Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:07.149114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:07.152438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:07.479527Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:07.720778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:08.300187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:08.570314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:08.767480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:08.837568Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:09.257524Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:09.297803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:09.990068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:12.970620Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:13.666330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:14.724213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:15.593109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:15.664534Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:15.749772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:15.906289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:15.942441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:16.020816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:16.140956Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:16.213198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:16.300632Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:16.403393Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:16.484892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:16.971796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:17.199503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:17.731400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:17.884062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:00:18.344660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:19.096411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:19.706627Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T17:00:19.770071Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T17:00:20.265204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:24.019834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:25.007696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:25.146167Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T17:00:26.269117Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T17:00:26.502925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:00:27.464271Z | Info | Live bytes: 1032.96MB Heap size: 3391.09MB +2024-07-01T17:01:10.532315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:11.186869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:11.514429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:11.920945Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:12.047018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:12.362983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:12.546426Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:12.834364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:12.967534Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:13.087821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:13.441308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:14.722126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:15.860503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:16.440098Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:16.492672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:17.832822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:18.436466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:19.367074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:19.682122Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:19.915764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:20.910297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:22.233964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:22.860181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:23.374796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:23.898611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:24.387498Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:24.513535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:24.619470Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:24.761030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:24.767936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:24.826971Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:25.007663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:25.096594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:25.177613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:01:25.295472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:25.968840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:27.466354Z | Info | Live bytes: 1202.56MB Heap size: 3391.09MB +2024-07-01T17:01:28.487043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:32.556219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:51.321261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:52.723612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:54.303595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:55.298767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:55.818187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:56.720996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:57.422919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:57.958395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:58.729329Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:01:59.502434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:00.012975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:00.526619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:01.076648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:01.654265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:02.473318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:03.003272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:03.686413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:04.243899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:04.751515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:05.367743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:05.989291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:09.808732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:10.697485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:11.268386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:12.010819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:12.611446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:13.192111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:13.784737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:14.699898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:15.239652Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:15.823288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:16.369325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:17.057765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:17.634565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:18.141519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:18.660318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:19.205816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:20.429707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:21.033664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:21.684094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:22.324868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:22.926908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:23.496616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:24.294135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:24.838104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:25.480959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:25.994926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:26.567140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:27.084265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:27.467416Z | Info | Live bytes: 874.87MB Heap size: 3391.09MB +2024-07-01T17:02:28.057042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:28.746216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:29.267822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:30.025343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:30.562324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:31.073214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:32.565831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-01T17:02:32.713097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:33.357975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:34.086169Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T17:02:34.135017Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T17:02:34.640431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:55.341574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:55.961088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:56.473941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-01T17:02:56.710875Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-01T17:03:27.498398Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:04:27.545570Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:05:27.596327Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:06:27.656236Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:07:27.717018Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:08:27.777409Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:09:27.837427Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:10:27.897357Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:11:27.934602Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:12:27.955484Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:13:28.016321Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:14:28.077061Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:15:28.138010Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:16:28.198420Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:17:28.259520Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:18:28.320296Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:19:28.380409Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:20:28.441285Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:21:28.501279Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:22:28.534211Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:23:28.594193Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:24:28.654313Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:25:28.714299Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:26:28.774339Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:27:28.835021Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:28:28.895686Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:29:28.925130Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:30:28.985445Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:31:29.024398Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:32:29.039485Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:33:29.099168Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:34:29.159751Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:35:29.220291Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:36:29.281191Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:37:29.342123Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:38:29.403048Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:39:29.421354Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:40:29.482292Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:41:29.542214Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:42:29.602347Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:43:29.638020Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:44:29.654155Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:45:29.715022Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:46:29.726323Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:47:29.755686Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:48:29.816628Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:49:29.877971Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:50:29.939327Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:51:30.000085Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:52:30.024927Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:53:30.086718Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:54:30.148500Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:55:30.210182Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:56:30.263475Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:57:30.324412Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:58:30.375318Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T17:59:30.436876Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T18:00:30.489745Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T18:01:30.551198Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T18:02:30.580782Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T18:03:30.641861Z | Info | Live bytes: 997.39MB Heap size: 3391.09MB +2024-07-01T18:04:17.715364Z | Error | Got EOF +2024-07-02 08:22:58.2250000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-02 08:22:58.2280000 [client] INFO Finding haskell-language-server +2024-07-02 08:22:58.2310000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:58.2310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:58.2380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-02 08:22:58.4990000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:58.4990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:58.5050000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-02 08:22:58.7450000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:58.7450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:58.7550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-02 08:22:59.0590000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:59.0590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:59.0680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-02 08:22:59.3140000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:59.3150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:59.3210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-02 08:22:59.3380000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:59.3380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:59.3460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-02 08:22:59.3630000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:59.3630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:59.3680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-02 08:22:59.3950000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-02 08:22:59.4440000 [client] INFO Checking for ghcup installation +2024-07-02 08:22:59.4450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:22:59.4500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-02 08:22:59.6570000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-02 08:22:59.6580000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-02 08:23:10.1510000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-02 08:23:10.2920000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-02 08:23:10.2920000 [client] INFO Checking for ghcup installation +2024-07-02 08:23:10.2920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:23:10.2970000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-02 08:23:10.3920000 [client] INFO Checking for ghcup installation +2024-07-02 08:23:10.3920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:23:10.3980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-02 08:23:10.4150000 [client] INFO Checking for ghcup installation +2024-07-02 08:23:10.4160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:23:10.4210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-02 08:23:10.4370000 [client] INFO Checking for ghcup installation +2024-07-02 08:23:10.4370000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:23:10.4420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-02 08:23:10.4570000 [client] INFO Checking for ghcup installation +2024-07-02 08:23:10.4570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:23:10.4610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-02 08:23:10.5860000 [client] ERROR Error executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' with error code 1 +2024-07-02 08:23:10.5860000 [client] ERROR stderr: ghcup: createFileLink:createSymbolicLink '../../bin/cabal-3.10.3.0' to '/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/cabal': already exists (File exists) + +2024-07-02 08:23:10.5860000 [client] ERROR Internal Error: `/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install` exited with exit code 1. + Consult the [Extensions Output](https://github.com/haskell/vscode-haskell#investigating-and-reporting-problems) + for details. +2024-07-02 08:23:10.5870000 [client] ERROR Error: `/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install` exited with exit code 1. + Consult the [Extensions Output](https://github.com/haskell/vscode-haskell#investigating-and-reporting-problems) + for details. + at /home/jordan/.vscode/extensions/haskell.haskell-2.4.4/dist/extension.js:1:22105 + at ChildProcess.exithandler (node:child_process:431:5) + at ChildProcess.emit (node:events:514:28) + at maybeClose (node:internal/child_process:1105:16) + at Socket. (node:internal/child_process:457:11) + at Socket.emit (node:events:514:28) + at Pipe. (node:net:337:12) +2024-07-02 08:24:04.9390000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-02 08:24:04.9410000 [client] INFO Finding haskell-language-server +2024-07-02 08:24:04.9420000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:04.9420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:04.9470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-02 08:24:05.0680000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:05.0680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:05.0750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-02 08:24:05.2570000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:05.2570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:05.2650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-02 08:24:05.4120000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:05.4120000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:05.4170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-02 08:24:05.5280000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:05.5280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:05.5330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-02 08:24:05.5480000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:05.5480000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:05.5530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-02 08:24:05.5670000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:05.5670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:05.5730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-02 08:24:05.5960000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-02 08:24:05.6450000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:05.6450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:05.6510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-02 08:24:05.7770000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-02 08:24:05.7780000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-02 08:24:08.0970000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-02 08:24:08.2460000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-02 08:24:08.2460000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:08.2460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:08.2510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-02 08:24:08.3460000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:08.3460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:08.3510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-02 08:24:08.3660000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:08.3660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:08.3710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-02 08:24:08.3860000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:08.3860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:08.3910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-02 08:24:08.4070000 [client] INFO Checking for ghcup installation +2024-07-02 08:24:08.4070000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 08:24:08.4130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-02 08:24:08.5070000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-02 08:24:08.5080000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-02 08:24:08.5080000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-02 08:24:08.5080000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-02 08:24:08.5080000 [client] INFO server environment variables: +2024-07-02 08:24:08.5080000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-02 08:24:08.5080000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-02 08:24:08.5080000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-02 08:24:08.5100000 [client] INFO Starting language server +2024-07-02T08:24:17.463415Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-02T08:24:17.464253Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-02T08:24:17.464454Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-02T08:24:17.466854Z | Info | Logging heap statistics every 60.00s +2024-07-02T08:24:17.474177Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-02T08:24:17.474614Z | Info | Starting server +2024-07-02T08:24:17.476314Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-02T08:24:17.583153Z | Info | Started LSP server in 0.11s +2024-07-02T08:24:18.807015Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs +2024-07-02T08:24:18.808076Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-02T08:24:19.216231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:24:19.216241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:24:20.314972Z | Info | Load cabal cradle using single file +2024-07-02T08:24:21.219224Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT21259-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-02T08:24:24.464105Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-648e747809904bf8a445e4ab5be3a6d6f62ad1c0 +2024-07-02T08:24:24.470027Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-02T08:25:17.517642Z | Info | Live bytes: 348.25MB Heap size: 1650.46MB +2024-07-02T08:26:17.548537Z | Info | Live bytes: 489.02MB Heap size: 1690.30MB +2024-07-02T08:27:17.585461Z | Info | Live bytes: 489.02MB Heap size: 1690.30MB +2024-07-02T08:28:17.645430Z | Info | Live bytes: 489.02MB Heap size: 1690.30MB +2024-07-02T08:28:28.770553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:29.292688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:31.713649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:33.620647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:34.239357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:35.915176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:39.390581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:40.142960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:40.394685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:40.572503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:42.782899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:43.290395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:43.794286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:44.646398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:45.211069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:45.809917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:46.176450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:47.402479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:47.611162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:47.686400Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:47.899229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:55.866798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:56.449216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:57.576100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:57.857033Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:58.060798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:58.559529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:58.644137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:59.083177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:28:59.346543Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:59.402097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:59.456549Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:28:59.505867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:01.900099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:02.253997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:08.077832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:08.223984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:08.234311Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:17.646892Z | Info | Live bytes: 660.74MB Heap size: 2118.12MB +2024-07-02T08:29:17.695603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:18.258509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:18.525036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:18.575003Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:18.776308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:18.817513Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:18.884692Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:18.923506Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:19.190995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:19.256430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:19.910403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:20.854511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:21.176047Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:21.347573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:21.871332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:22.486240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:22.933399Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:23.444467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:23.961685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:24.428434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:29.982821Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:30.171891Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:30.537102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:31.069723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:31.153371Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:29:31.526494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:29:32.573505Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:29:32.638770Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:29:33.044351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:30:17.692121Z | Info | Live bytes: 792.88MB Heap size: 2118.12MB +2024-07-02T08:31:17.753086Z | Info | Live bytes: 792.88MB Heap size: 2118.12MB +2024-07-02T08:31:45.807071Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:45.947175Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.045062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.162208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:31:46.192598Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.382382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.483156Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.605209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.689401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.749880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:31:46.784270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:46.900383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:31:47.308413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:31:48.196671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:31:48.768776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:31:56.060886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:31:56.756719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:32:17.773857Z | Info | Live bytes: 925.57MB Heap size: 2118.12MB +2024-07-02T08:33:01.843929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:15.743738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:17.777338Z | Info | Live bytes: 557.89MB Heap size: 2400.19MB +2024-07-02T08:33:31.455183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:41.506684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:44.410409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:45.713927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:46.268381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:47.692521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:33:48.530811Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:33:48.706447Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:33:49.111967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:34:17.782008Z | Info | Live bytes: 684.07MB Heap size: 2400.19MB +2024-07-02T08:34:26.195311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:35:17.783595Z | Info | Live bytes: 707.95MB Heap size: 2400.19MB +2024-07-02T08:36:17.844554Z | Info | Live bytes: 707.95MB Heap size: 2400.19MB +2024-07-02T08:37:17.905788Z | Info | Live bytes: 707.95MB Heap size: 2400.19MB +2024-07-02T08:37:35.032503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:37:35.863678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:37:37.866482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:37:47.538582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:37:48.551516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:37:54.191852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:37:54.554860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:13.534968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:13.974877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:14.567294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:16.423689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:17.765739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:17.907211Z | Info | Live bytes: 593.05MB Heap size: 2519.73MB +2024-07-02T08:38:18.529463Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:38:18.587466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:18.593230Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:38:37.971618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:38.532932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:39.162656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:39.652731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:40.330086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:40.909347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:41.998794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:42.568669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:43.222720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:43.780194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:54.992783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:55.490434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:56.931467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:57.352945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:38:57.381224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:38:57.852380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:04.588159Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:39:04.622272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:04.765772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:39:04.935779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:39:05.045528Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:39:05.104159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:11.671397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:17.909370Z | Info | Live bytes: 881.96MB Heap size: 2519.73MB +2024-07-02T08:39:31.689512Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:39:31.746910Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:39:32.152210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:48.781656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:49.279173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:49.870972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:54.969143Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:39:55.328031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:57.380450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:57.907360Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:39:57.907666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:39:58.403967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:40:07.288129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:40:08.612024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:40:08.710641Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:40:08.809562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:40:08.915269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:40:08.964152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:40:09.156581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:40:09.555642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:40:10.088866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:40:10.288349Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:40:17.916739Z | Info | Live bytes: 1077.65MB Heap size: 2519.73MB +2024-07-02T08:41:04.083100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:04.981369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:05.451835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:07.781712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:07.911659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:07.918839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:08.280633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:08.620111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:08.653337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:08.773536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:08.859330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:09.061514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:09.145594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:09.502597Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:09.703142Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:09.868428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:09.868449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:09.929294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:10.056508Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:10.136463Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:10.303916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:11.602327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:11.681418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:12.033404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:13.710081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:14.117921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:41:14.208650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:17.919486Z | Info | Live bytes: 609.60MB Heap size: 2693.79MB +2024-07-02T08:41:34.431443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:41:34.924111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:42:17.963436Z | Info | Live bytes: 640.45MB Heap size: 2693.79MB +2024-07-02T08:43:17.997744Z | Info | Live bytes: 640.45MB Heap size: 2693.79MB +2024-07-02T08:44:18.000355Z | Info | Live bytes: 640.45MB Heap size: 2693.79MB +2024-07-02T08:45:18.062020Z | Info | Live bytes: 646.11MB Heap size: 2693.79MB +2024-07-02T08:46:18.123441Z | Info | Live bytes: 646.11MB Heap size: 2693.79MB +2024-07-02T08:47:18.185131Z | Info | Live bytes: 646.11MB Heap size: 2693.79MB +2024-07-02T08:48:18.247627Z | Info | Live bytes: 646.11MB Heap size: 2693.79MB +2024-07-02T08:49:18.309297Z | Info | Live bytes: 646.11MB Heap size: 2693.79MB +2024-07-02T08:50:16.545421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:16.557762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:16.738509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:16.937411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:17.099352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:17.116327Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:17.338518Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:17.435757Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:17.561222Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:17.623447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:17.706548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:17.739713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:17.829267Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:18.235535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:18.310751Z | Info | Live bytes: 697.35MB Heap size: 2693.79MB +2024-07-02T08:50:18.518968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:18.709659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:19.376800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:19.491980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:50:19.863315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:21.492788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:22.141269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:22.677262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:50:32.136533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:51:18.358217Z | Info | Live bytes: 848.07MB Heap size: 2693.79MB +2024-07-02T08:52:18.419400Z | Info | Live bytes: 848.07MB Heap size: 2693.79MB +2024-07-02T08:53:18.438348Z | Info | Live bytes: 848.07MB Heap size: 2693.79MB +2024-07-02T08:54:18.469107Z | Info | Live bytes: 848.07MB Heap size: 2693.79MB +2024-07-02T08:55:18.529851Z | Info | Live bytes: 848.07MB Heap size: 2693.79MB +2024-07-02T08:56:18.583032Z | Info | Live bytes: 848.07MB Heap size: 2693.79MB +2024-07-02T08:57:18.644213Z | Info | Live bytes: 848.07MB Heap size: 2693.79MB +2024-07-02T08:58:07.611214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:58:15.160144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:58:18.648538Z | Info | Live bytes: 895.71MB Heap size: 2693.79MB +2024-07-02T08:58:28.258331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:58:37.033867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:58:37.667350Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T08:58:55.582584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:18.672560Z | Info | Live bytes: 1006.21MB Heap size: 2693.79MB +2024-07-02T08:59:31.691724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:32.114892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:32.543863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:32.626721Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:59:32.991520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:33.493827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:33.879114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:59:33.935539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:34.576418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:35.788750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:36.221463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:38.888597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:39.364969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:39.576723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T08:59:39.839128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:40.522938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:40.973963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:41.533525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T08:59:41.995332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:00:18.709606Z | Info | Live bytes: 1059.90MB Heap size: 2693.79MB +2024-07-02T09:00:33.448670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:00:34.428828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:01:18.729908Z | Info | Live bytes: 598.04MB Heap size: 2704.28MB +2024-07-02T09:01:20.781571Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:01:21.120997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:01:21.969794Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:01:22.322754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:01:23.172522Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:01:32.671905Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:01:33.018570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:01:33.765762Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:02:18.769602Z | Info | Live bytes: 691.15MB Heap size: 2704.28MB +2024-07-02T09:02:59.950518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:00.377193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:00.843024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:01.379761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:01.863872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:01.998921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:02.366361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:04.085797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:05.052613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:05.498066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:06.847574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:07.261542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:07.811759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:08.346354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:09.120936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:09.180117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:09.766315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:10.219293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:10.775899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:13.963759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:14.141788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:14.773269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:15.282865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:15.702561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:16.562329Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:16.933661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:17.647418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:17.977777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:18.347384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:18.771489Z | Info | Live bytes: 718.36MB Heap size: 2704.28MB +2024-07-02T09:03:19.068210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:19.771624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:19.801333Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:21.192762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:21.873990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:22.836780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:23.448688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:23.965785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:24.200420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:25.737640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:26.206565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:27.296311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:27.753869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:28.209585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:28.755445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:31.463475Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:31.827778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:32.102344Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:32.159468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:32.260704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:32.326414Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:32.389164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:32.555104Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:32.615727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:03:32.701106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:03:33.249433Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:04:08.392573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:04:08.748556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:04:10.291465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:04:10.648717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:04:10.852305Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:04:18.776936Z | Info | Live bytes: 986.55MB Heap size: 2704.28MB +2024-07-02T09:05:18.837862Z | Info | Live bytes: 986.55MB Heap size: 2704.28MB +2024-07-02T09:06:18.898275Z | Info | Live bytes: 986.55MB Heap size: 2704.28MB +2024-07-02T09:07:18.958855Z | Info | Live bytes: 986.55MB Heap size: 2704.28MB +2024-07-02T09:08:19.019747Z | Info | Live bytes: 986.55MB Heap size: 2704.28MB +2024-07-02T09:08:51.780114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:52.273801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:52.701603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:53.122520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:53.537380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:53.961567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:54.823669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:55.520511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:56.021086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:56.445789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:56.870981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:57.286271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:08:58.360775Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:09:14.556650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:19.025530Z | Info | Live bytes: 1128.79MB Heap size: 2704.28MB +2024-07-02T09:09:22.965082Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.009551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.039071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:23.198262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.266418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.349241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.390615Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.575615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:23.703463Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.847448Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:23.948676Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:24.072093Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:24.073316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:24.240427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:24.340925Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:24.448275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:24.571316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:24.621141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:24.694345Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:25.077806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:25.644733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:25.838482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:26.154864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:26.189548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:26.326696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:26.341706Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:26.477630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:26.576120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:26.646217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:26.738166Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:26.738839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:26.808094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:27.206340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:27.241191Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:09:27.441497Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:09:27.832906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:33.066604Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:33.606759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:33.616293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:34.102386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:34.608262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:34.977190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:42.180790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:42.664588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:09:42.685087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:46.898953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:48.325948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:50.006376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:51.023119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:51.469831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:53.439523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:58.291607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:09:58.817483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:00.710882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:05.825644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:06.684160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:07.177281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:07.688829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:19.037712Z | Info | Live bytes: 895.05MB Heap size: 2795.50MB +2024-07-02T09:10:27.167380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:28.214922Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:28.413782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:28.421532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:28.586621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:28.676492Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:28.844120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:28.905361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:28.966832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:30.135079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:30.756316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:31.204072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:35.952483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:36.402599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:36.849007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:37.401077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:37.502640Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:37.735958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:39.316005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:39.465571Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:39.608005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:39.700344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:39.838855Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:39.992995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:40.143894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:40.218546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:40.685498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:40.852036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:40.945390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:41.061919Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:41.107944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:41.171919Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:41.219753Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:41.426704Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:41.555178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:41.833890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:42.043040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:42.156576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:10:42.211022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:43.376996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:43.807019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:10:45.017272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:11:09.612445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:11:10.845745Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:10.946916Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.056774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.199413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:11:11.219313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.393657Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.457461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.583252Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.656747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.743707Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:11.754451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:11:11.851959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:11:12.259737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:11:19.045563Z | Info | Live bytes: 1016.89MB Heap size: 2795.50MB +2024-07-02T09:11:31.539162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:11:32.142578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:06.693052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:07.349018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:09.177605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:09.920094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:12.866256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:13.696609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:17.794176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:19.047559Z | Info | Live bytes: 664.85MB Heap size: 2795.50MB +2024-07-02T09:12:20.405191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:20.832177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:24.476373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:27.745102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:28.319489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:31.143045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:32.593678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:35.589221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:36.102114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:12:39.310177Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:12:39.368685Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:12:39.773387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:13:19.086360Z | Info | Live bytes: 886.96MB Heap size: 2795.50MB +2024-07-02T09:14:19.146303Z | Info | Live bytes: 886.96MB Heap size: 2795.50MB +2024-07-02T09:15:19.207140Z | Info | Live bytes: 886.96MB Heap size: 2795.50MB +2024-07-02T09:15:40.020892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:40.830435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:42.073340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:42.193474Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:42.330165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:43.597993Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:43.845107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:43.976579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:43.988251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:44.468343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:45.097014Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:45.514738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:47.615165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:47.713044Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:47.846064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:50.300220Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:50.401788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:50.582924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:50.888436Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:51.116342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:51.200384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:51.265906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:51.728005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:52.694056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:53.161528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:53.486801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:53.617455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:54.094338Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:15:54.175333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:54.595779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:55.060388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:55.537054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:57.241178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:15:59.599813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:16:00.902144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:16:01.582057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:16:02.003739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:16:08.349920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:16:19.219862Z | Info | Live bytes: 967.50MB Heap size: 2795.50MB +2024-07-02T09:16:26.019202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:16:54.109569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:16:54.527847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:03.260354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:03.726008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:03.932936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:04.606581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:07.717389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:14.068294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:14.877971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:15.357982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:19.221065Z | Info | Live bytes: 987.17MB Heap size: 2795.50MB +2024-07-02T09:17:21.884743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:23.799067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:25.585631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:26.161306Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:26.195723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:26.230415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:26.663502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:27.104837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:30.662993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:31.443971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:32.029762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:32.597357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:32.652232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:32.892621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:33.083458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:33.097993Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:33.157765Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:33.221553Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:33.502415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:33.529858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:34.545302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:35.211592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:35.524196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:35.682907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:36.077836Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:36.208810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:36.832624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:37.374454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:37.790023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:38.329088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:38.800133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:39.131199Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:39.197562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:39.490738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:39.965306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:40.591919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:40.884655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:41.250784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:41.747110Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:41.766538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:41.793959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:17:42.252768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:42.724894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:17:49.691224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:17.199236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:19.243339Z | Info | Live bytes: 1158.66MB Heap size: 2795.50MB +2024-07-02T09:18:43.514845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:45.385835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:45.903195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:46.495772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:46.762970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:18:46.959530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:53.406913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:53.969541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:18:57.672945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:19:19.249732Z | Info | Live bytes: 645.71MB Heap size: 2795.50MB +2024-07-02T09:19:57.638017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:19:58.174988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:19:58.714050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:19:59.515692Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:19:59.709200Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:19:59.872565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:19:59.882104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:00.122277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:00.289555Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:00.455026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:00.493235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:00.739414Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:00.869485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:00.941459Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:01.099499Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:01.120774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:01.916354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:02.013486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:20:02.387083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:03.087878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:03.543795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:04.053471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:08.759832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:17.069762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:19.253406Z | Info | Live bytes: 887.80MB Heap size: 2795.50MB +2024-07-02T09:20:44.925900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:20:54.286897Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:20:54.871746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:06.116530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:13.586722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:17.810952Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:21:19.256218Z | Info | Live bytes: 1015.34MB Heap size: 2795.50MB +2024-07-02T09:21:24.094008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:26.262138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:26.421956Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:21:27.677340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:28.423592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:28.944814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:31.876246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:33.829139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:37.450550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:38.871180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:38.884866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:21:39.901855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:43.534042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:44.422094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:21:44.558157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:21:44.673950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:21:44.754066Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:21:44.803727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:44.875209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:21:45.021049Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:21:45.284915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:47.963732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:48.686186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:49.100592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:49.537903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:50.391257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:51.213212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:51.961194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:52.425993Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:21:52.603046Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:21:53.006200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:21:56.426030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:10.377098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:19.257704Z | Info | Live bytes: 1062.71MB Heap size: 2795.50MB +2024-07-02T09:22:21.855226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:23.921568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:26.615126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:28.539566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:33.750478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:35.596627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:54.985271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:22:59.631432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:03.373786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:06.915687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:12.913677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:19.265031Z | Info | Live bytes: 1024.95MB Heap size: 2796.55MB +2024-07-02T09:23:20.607181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:25.846538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:35.939207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:38.606052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:23:39.766459Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:24:03.066859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:04.910293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:24:04.999915Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:24:05.081419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:24:05.224317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:24:05.277051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:06.125269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:24:06.522401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:07.051800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:07.121794Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:24:07.184053Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:24:07.578975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:12.006556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:13.431136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:14.874314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:15.556015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:24:16.349429Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:24:19.267352Z | Info | Live bytes: 1012.73MB Heap size: 2829.06MB +2024-07-02T09:25:00.556781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:01.075535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:01.872374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:16.904743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:16.962845Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.034427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:17.112784Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.177257Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.247645Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.286672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.498515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:17.574019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.707129Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.796702Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.913207Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:17.945074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:18.080915Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:18.190105Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:18.283930Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:18.375059Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:18.461970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:18.495746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:18.885379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:19.216984Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:19.267934Z | Info | Live bytes: 1065.20MB Heap size: 2829.06MB +2024-07-02T09:25:19.395755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:19.992906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:20.133389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:20.364307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:20.592054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:20.772406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:20.776442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:20.992322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:21.138014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:21.213363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:21.319866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:21.392971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:21.410253Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:21.511778Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:25:21.807297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:21.980796Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:25:22.174868Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:25:22.555094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:48.818387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:50.294284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:51.092178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:58.559283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:59.146139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:25:59.631255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:01.802615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:02.224118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:02.626567Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:26:02.642391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:09.172731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:19.278261Z | Info | Live bytes: 635.96MB Heap size: 2834.30MB +2024-07-02T09:26:23.079345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:23.798845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:24.421278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:24.839063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:25.309305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:25.324966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:26:25.408104Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:26:25.789373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:25.818517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:26:26.472437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:26.888246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:33.110343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:52.836646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:53.498138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:53.910351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:26:55.509863Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:27:05.906799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:06.494537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:07.938990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:08.652916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:09.090602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:09.225399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:09.325681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:09.411016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:09.494588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:09.587373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:09.597651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:09.699097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:10.086430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:10.604181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:12.194590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:13.075523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:13.207190Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:13.406615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:14.995482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:15.172496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:15.295639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:15.369485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:15.728125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:19.283245Z | Info | Live bytes: 865.11MB Heap size: 2834.30MB +2024-07-02T09:27:19.736348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:20.348848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:20.811166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:22.004807Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.050130Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.159949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:22.222014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.274399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.439648Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.521206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.595751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:22.724200Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.795323Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:22.938160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:23.012892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:23.090559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:23.216132Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:23.301357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:23.405241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:23.584114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:24.336022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:24.409938Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:24.477944Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:24.569344Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:24.589690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:24.883806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:24.962750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:25.102881Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:25.218251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:25.259537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:25.282975Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:26.531030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:26.590278Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:26.711219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:26.823669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:27.036916Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:27.122712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:27.253886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:27.341940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:27.408550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:27.410067Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:28.715489Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:27:54.934132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:55.378677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:56.011665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:27:56.370743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:56.821340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:57.259473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:57.926327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:27:58.583320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:28:04.495355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:28:06.458418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:28:19.297010Z | Info | Live bytes: 1023.44MB Heap size: 2834.30MB +2024-07-02T09:28:48.596925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:28:57.169974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:01.423210Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:01.476869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:01.544084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:01.627946Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:01.691062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:01.746135Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:01.803715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:02.007410Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:02.408678Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:29:02.515764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:02.612453Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:29:03.004186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:12.574581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:12.609428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:12.685238Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:13.091186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:13.262924Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:13.318330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:29:13.492083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:14.506881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:14.963711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:15.480515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:19.301423Z | Info | Live bytes: 610.48MB Heap size: 2877.29MB +2024-07-02T09:29:25.315615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:25.560565Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:29:40.950852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:41.005681Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:29:41.194081Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:29:41.579732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:57.839016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:29:59.013300Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:29:59.676519Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:30:00.904741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:30:19.320507Z | Info | Live bytes: 732.88MB Heap size: 2877.29MB +2024-07-02T09:30:26.746192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:30:28.003128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:30:35.534663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:30:37.944280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:30:38.989383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:30:39.048862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:30:39.346403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:30:39.800171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:30:40.258777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:19.326184Z | Info | Live bytes: 763.43MB Heap size: 2877.29MB +2024-07-02T09:31:31.332661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:33.032244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:33.813743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:34.344277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:34.968332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:37.845464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:38.721142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:44.993294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:47.377028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:47.482980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:47.715097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:47.726017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:47.892954Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:48.070192Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:48.191300Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:48.265539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:48.278277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:48.462214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:48.787135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:48.978345Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:49.387202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:49.825679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:49.904751Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:31:50.276764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:51.018551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:51.435646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:51.944414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:52.459023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:52.864094Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:31:53.445313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:31:59.654448Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:32:00.015271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:32:19.347204Z | Info | Live bytes: 813.41MB Heap size: 2877.29MB +2024-07-02T09:33:04.433692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:05.098011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:05.291342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:05.380129Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:05.552551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:05.603415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:05.670618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:05.759474Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:05.791781Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:06.127621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:06.600282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:06.606918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:09.148872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:09.653251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:09.669213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:10.800615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:12.406459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:13.472241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:14.389672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:14.893020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:14.896337Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:15.129605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:15.336736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:15.864627Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:16.101772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:16.302605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:16.549097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:17.124317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:17.725571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:18.216108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:19.138460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:19.348967Z | Info | Live bytes: 846.85MB Heap size: 2877.29MB +2024-07-02T09:33:19.610688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:21.231889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:21.682602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:27.765894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:33.438826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:33.440945Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:33.484662Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:33.669008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:33.706091Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:33.864971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:33.887859Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:33.989833Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:33:34.365375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:33:47.471899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:07.714677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:08.383607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:09.007891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:09.462418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:09.621041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:09.672306Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:09.782843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:10.846546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:11.272194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:11.687028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:12.219572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:12.850852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:13.283037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:19.357023Z | Info | Live bytes: 896.64MB Heap size: 2877.29MB +2024-07-02T09:34:26.070451Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.165881Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.261003Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.339578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:26.454278Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.560470Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.630612Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.719772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.817355Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:26.829806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:26.902544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:27.312487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:31.268623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:35.171457Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:36.827546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:38.585883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:39.100354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:40.214348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:42.253432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:42.717124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:44.017823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:44.479052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:44.967081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:48.997272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:49.495523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:50.045512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:53.652765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:54.097472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:54.786534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:56.283131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:56.988543Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:34:57.345425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:57.927875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:58.389828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:58.865933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:34:59.761085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:00.030533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:35:00.248312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:00.847464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:01.933527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:02.390612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:02.814837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:03.274778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:11.753572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:16.035335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:16.476580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:18.302864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:18.871756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:19.359916Z | Info | Live bytes: 974.16MB Heap size: 2877.29MB +2024-07-02T09:35:23.160725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:24.702750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:25.846694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:29.146853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:33.355252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:38.448690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:45.502829Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:35:46.093303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:49.187087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:50.255518Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:35:50.532448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:51.144331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:35:51.520836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:51.778246Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:35:51.870994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:35:52.076787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:52.315066Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:35:52.465710Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:35:52.699805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:53.518849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:53.949107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:35:54.808406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:00.219447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:00.837177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:02.073423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:06.100772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:06.879934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:07.159863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:07.221422Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:07.531269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:07.985994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:09.940956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:10.587590Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:36:10.638188Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:36:11.044036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:13.032195Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:13.392047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:14.862923Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:36:15.569113Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:36:15.972110Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:36:17.062216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:19.361076Z | Info | Live bytes: 1006.35MB Heap size: 2877.29MB +2024-07-02T09:36:19.472005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:20.116921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:20.685072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:21.106196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:22.469084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:22.730013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:22.938599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:23.291102Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:23.429458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:24.018033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:24.028897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:24.467877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:26.757685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:27.230923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:27.403787Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:36:27.988687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:51.009905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:51.681433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:52.401204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:52.960784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:53.889602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:54.084242Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:54.145437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:54.214698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:54.441868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:55.031702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:55.389027Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:36:55.491049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:36:56.093851Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:37:04.660600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:05.598990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:06.030647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:06.054267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:06.089666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:06.298220Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:06.353099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:06.420556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:06.559455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:06.733173Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:06.993787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:07.667663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:08.187493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:08.282271Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:08.659576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:08.784186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:09.140029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:09.594524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:09.780936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:09.856941Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:37:10.102317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:10.639269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:11.126547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:11.717469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:15.355597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:16.805377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:18.819032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:19.361891Z | Info | Live bytes: 1069.77MB Heap size: 2884.63MB +2024-07-02T09:37:19.532426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:19.948730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:20.435535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:37:20.836637Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:37:21.419539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:38:06.086790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:38:06.134793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:38:06.376546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:38:10.305041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:38:10.390571Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:38:10.457430Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:38:10.674371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:38:19.372352Z | Info | Live bytes: 1094.37MB Heap size: 2888.83MB +2024-07-02T09:38:26.427186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:38:28.098872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:38:45.735417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:03.356359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:08.319691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:16.952823Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:39:17.049461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:17.091837Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:39:17.144940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:39:17.233087Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:39:17.267686Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:39:17.470779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:17.984923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:18.361159Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:39:18.543716Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:39:18.935276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:19.375871Z | Info | Live bytes: 1207.19MB Heap size: 2888.83MB +2024-07-02T09:39:31.403806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:34.510656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:35.439770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:44.654526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:45.151786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:45.842389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:39:47.092540Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:39:58.298211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:00.220482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:00.770186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:01.139496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:01.242956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:01.744439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:01.858114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:02.490450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:03.320031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:03.943862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:04.398372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:05.123424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:06.606693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:06.746851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:07.072293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:07.619323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:08.060351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:08.818063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:09.236370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:09.715351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:09.737547Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:09.936176Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:10.083550Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:10.168848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:10.302894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:10.460750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:10.778839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:10.825745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:10.852495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:10.947683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:11.306333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:11.526556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:40:11.935809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:12.589355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:13.032089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:13.686066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:14.299927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:15.468543Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:16.047909Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:40:19.380304Z | Info | Live bytes: 688.21MB Heap size: 2959.08MB +2024-07-02T09:40:25.545220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:26.511078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:29.870556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:30.301018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:30.862733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:31.682166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:34.184016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:37.039363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:37.813846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:38.669023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:38.926865Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:40:39.514094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:54.624819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:56.602056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:40:57.655265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:00.824881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:02.174744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:03.201775Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:03.770821Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:41:13.054903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:13.990251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:14.471704Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:41:19.385865Z | Info | Live bytes: 722.76MB Heap size: 2959.08MB +2024-07-02T09:41:54.073180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:56.583234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:41:59.061055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:00.304773Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:42:01.760193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:03.105962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:03.536693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:03.569377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:04.398350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:04.420089Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:04.949218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:05.473266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:06.462855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:06.882009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:07.418071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:08.000935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:08.367922Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:08.557019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:08.616432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:08.776324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:08.859408Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:09.142545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:09.251457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:09.618998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:09.694289Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:09.749430Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:09.855849Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:09.959644Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:10.061938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:11.005958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:11.649632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:12.137444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:13.659289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:15.313179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:15.820417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:16.265249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:17.092774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:17.579507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:18.054492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:19.226473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:19.387224Z | Info | Live bytes: 763.96MB Heap size: 2959.08MB +2024-07-02T09:42:19.476819Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:19.676479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:20.171008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:20.399390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:20.784292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:21.574319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:22.204383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:22.973582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:23.432881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:23.973398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:24.619828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:25.911753Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:26.098549Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:26.173691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:26.259136Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:26.353041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:26.555078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:26.622434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:26.839680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:26.918021Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:27.007485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:27.142317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:27.210489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:28.034188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:28.448154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:28.906082Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:29.376264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:29.846463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:30.399216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:31.068446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:31.720793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:31.963100Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:32.141594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:32.762715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:32.799487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:33.402111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:33.475392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:33.936378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:34.414729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:35.092366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:35.538790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:36.286809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:36.764828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:36.920250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.102226Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.181067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:37.237252Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.352157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.451707Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.556862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.601075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:37.627902Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.731368Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:37.846028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:38.094855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:39.410202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:39.833863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:40.266528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:41.008657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:41.981700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:42.955658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:43.410770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:43.924537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:44.772880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:45.095790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:45.238027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:45.755213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:45.826331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:46.289425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:46.777335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:49.634103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:50.090211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:50.820994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:51.277861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:51.413031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:51.528781Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:51.716979Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:51.772301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:51.815279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:51.889686Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:52.008647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:52.099531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:52.187411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:52.189585Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:52.289954Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:52.398388Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:42:52.654071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:53.394791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:54.200720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:54.671778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:55.413667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:56.741884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:57.206946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:42:57.381329Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:42:57.972776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:43:19.409905Z | Info | Live bytes: 898.69MB Heap size: 2959.08MB +2024-07-02T09:44:06.777072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:44:19.424380Z | Info | Live bytes: 898.69MB Heap size: 2959.08MB +2024-07-02T09:44:24.262138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:45:01.800118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:45:03.625231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:45:05.905918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:45:06.918583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:45:15.649697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:45:19.429533Z | Info | Live bytes: 920.56MB Heap size: 2959.08MB +2024-07-02T09:45:20.264358Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:45:20.318336Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:45:20.379850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:45:20.480332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T09:45:20.682542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:46:19.439864Z | Info | Live bytes: 936.02MB Heap size: 2959.08MB +2024-07-02T09:46:42.489236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:46:44.658201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:47:19.476750Z | Info | Live bytes: 940.65MB Heap size: 2959.08MB +2024-07-02T09:48:19.537540Z | Info | Live bytes: 940.65MB Heap size: 2959.08MB +2024-07-02T09:49:19.598925Z | Info | Live bytes: 940.65MB Heap size: 2959.08MB +2024-07-02T09:50:19.660699Z | Info | Live bytes: 940.65MB Heap size: 2959.08MB +2024-07-02T09:51:19.721911Z | Info | Live bytes: 940.65MB Heap size: 2959.08MB +2024-07-02T09:52:10.613108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:52:16.748346Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:52:19.725763Z | Info | Live bytes: 928.53MB Heap size: 2959.08MB +2024-07-02T09:53:00.157132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:53:00.604324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:53:01.309816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:53:01.994083Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:53:17.003001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:53:17.590415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:53:18.440698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:53:18.719657Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:53:19.728524Z | Info | Live bytes: 935.68MB Heap size: 2959.08MB +2024-07-02T09:53:27.575121Z | Info | LSP: received shutdown +2024-07-02T09:53:27.586175Z | Error | Got EOF +2024-07-02T09:53:36.249343Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-02T09:53:36.250640Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-02T09:53:36.250844Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-02T09:53:36.253542Z | Info | Logging heap statistics every 60.00s +2024-07-02T09:53:36.260247Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-02T09:53:36.260626Z | Info | Starting server +2024-07-02T09:53:36.262072Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-02T09:53:36.320125Z | Info | Started LSP server in 0.06s +2024-07-02T09:53:37.606353Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs +2024-07-02T09:53:37.606973Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-02T09:53:38.018871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:53:39.069505Z | Info | Load cabal cradle using single file +2024-07-02T09:53:40.025036Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT96586-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-02T09:53:43.408325Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-648e747809904bf8a445e4ab5be3a6d6f62ad1c0 +2024-07-02T09:53:43.414748Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-02T09:54:36.304434Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T09:55:36.365459Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T09:56:36.426212Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T09:56:50.626976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:56:54.900839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T09:56:56.515330Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T09:57:36.467287Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T11:27:23.411180Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T11:28:23.472894Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T11:29:23.510047Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T11:30:23.547630Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T11:31:23.608744Z | Info | Live bytes: 345.26MB Heap size: 1650.46MB +2024-07-02T11:32:09.863894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:32:23.609774Z | Info | Live bytes: 480.52MB Heap size: 1701.84MB +2024-07-02T11:32:23.623556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:32:24.052262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:32:25.023887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:32:36.540114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:32:39.016354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:32:54.855202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:01.569720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:02.045472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:02.645128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:10.437830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:11.163923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:22.426092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:23.612438Z | Info | Live bytes: 521.40MB Heap size: 1779.43MB +2024-07-02T11:33:28.332833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:28.827245Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:29.550898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:39.652374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:41.301664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:33:41.717466Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:33:42.304044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:05.972805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:13.551946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:16.238521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:16.660088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:17.820989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:17.988180Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:34:19.741511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:22.530907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:34:23.615123Z | Info | Live bytes: 526.16MB Heap size: 1788.87MB +2024-07-02T11:34:48.865725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:04.258569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:04.878744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:05.407619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:06.078190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:06.533937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:07.270907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:07.941490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:08.862080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:09.541972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:10.069923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:10.830403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:11.726274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:12.430602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:12.846197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:13.806205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:35:23.619398Z | Info | Live bytes: 491.34MB Heap size: 2501.90MB +2024-07-02T11:36:00.001689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:36:03.332809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:36:06.259518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:36:08.779042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:36:15.628415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:36:18.379317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:36:23.621184Z | Info | Live bytes: 617.98MB Heap size: 2501.90MB +2024-07-02T11:36:44.361060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:36:51.764901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:05.467561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:05.978587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:06.897696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:08.425594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:08.858330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:19.267293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:19.302026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:20.487697Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:20.578937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:20.855864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:21.279270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:22.479113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:22.934732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:23.624022Z | Info | Live bytes: 902.54MB Heap size: 2501.90MB +2024-07-02T11:37:25.398067Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:37:31.605034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:32.249482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:32.282120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:32.473238Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:32.762483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:32.845243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:32.959175Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:33.047045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:33.332786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:37.734883Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:37.801927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:37.822552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:38.237121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:40.001932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:40.469319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:42.432424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:42.483653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:42.491029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:42.574470Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:42.938699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:43.784392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:44.213109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:48.112340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:48.120283Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:48.198191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:48.565237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:49.244727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:51.622633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:51.672176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:51.688734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:51.760593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:52.127784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:56.047434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:56.640396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:57.098478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:37:57.197699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:57.260653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:57.395806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:37:57.555786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:38:00.276047Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:38:12.523433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:38:23.636648Z | Info | Live bytes: 913.43MB Heap size: 2518.68MB +2024-07-02T11:38:25.489749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:38:26.183094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:38:26.778808Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-02T11:38:26.801841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:38:26.941566Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-02T11:38:27.346702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:39:23.692548Z | Info | Live bytes: 736.22MB Heap size: 2707.42MB +2024-07-02T11:40:23.754187Z | Info | Live bytes: 736.22MB Heap size: 2707.42MB +2024-07-02T11:41:09.206073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:10.112053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:10.774575Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:11.206956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:11.693282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:12.179918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:13.455943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:13.915611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:17.344995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:17.999460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:22.616574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:23.134926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:23.755811Z | Info | Live bytes: 932.39MB Heap size: 2707.42MB +2024-07-02T11:41:25.401799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:32.442038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:32.791920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:33.229871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:35.466183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:37.014354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:37.230919Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:37.416725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:37.509756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:37.591976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:38.603158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:39.360883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:46.553982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:54.416501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:54.458751Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:54.579029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:54.586700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:54.650457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:54.712396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:54.750114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:41:55.034678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:55.376456Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:41:55.488506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:41:55.562904Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:41:55.952189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:05.347718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:05.437886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:05.890291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:07.108334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:07.161132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:07.437479Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:07.511058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:07.808683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:12.598840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:13.092152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:13.601434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:14.237753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:14.787939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:16.199852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:16.377518Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:16.526171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:16.669140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:16.992517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:17.234233Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:17.352247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:17.363576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:22.562995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:22.969022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:23.337287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:23.757086Z | Info | Live bytes: 826.77MB Heap size: 2946.50MB +2024-07-02T11:42:23.789205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:24.334724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:24.782988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:25.196356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:25.663398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:26.214903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:26.372395Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:26.446245Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:26.534661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:26.652993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:47.356466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:48.462674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:49.044673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:49.373416Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:49.726777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:50.146771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:50.763294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:51.553281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:52.480960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:52.554430Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:52.793056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:52.871734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:42:52.921207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:53.521212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:42:57.649307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:43:01.309792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:43:07.407028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:43:08.069238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:43:08.620740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:43:09.969882Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:43:10.151458Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:43:10.555649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:43:18.259759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:43:18.888043Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:43:23.761437Z | Info | Live bytes: 813.07MB Heap size: 2946.50MB +2024-07-02T11:44:23.822537Z | Info | Live bytes: 813.07MB Heap size: 2946.50MB +2024-07-02T11:44:46.382761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:45:23.866061Z | Info | Live bytes: 813.07MB Heap size: 2946.50MB +2024-07-02T11:46:23.912335Z | Info | Live bytes: 829.12MB Heap size: 2946.50MB +2024-07-02T11:46:55.070680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:46:55.622233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:46:56.377712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:46:56.810637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:46:57.376955Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:46:57.747400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:46:58.210156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:46:58.721658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:46:59.220684Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:46:59.229822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:47:01.479766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:47:23.936668Z | Info | Live bytes: 996.39MB Heap size: 2946.50MB +2024-07-02T11:47:41.255729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:47:41.512525Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:47:41.589128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:47:47.267582Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:47:47.470763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:07.875851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:08.331801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:09.796095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:11.037894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:23.950808Z | Info | Live bytes: 1138.67MB Heap size: 2946.50MB +2024-07-02T11:48:34.997232Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:48:35.284980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:35.320602Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:48:35.421685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:48:35.503020Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:48:35.598053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:48:35.792307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:35.957451Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:48:36.099883Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:48:36.323834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:37.494686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:37.919242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:38.372150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:40.481435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:40.949188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:48:41.542183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:23.993786Z | Info | Live bytes: 671.39MB Heap size: 2984.25MB +2024-07-02T11:49:35.252599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:35.776093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:36.195069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:36.634007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:37.965544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:38.569471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:39.029386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:39.797412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:41.181339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:41.601784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:42.347967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:42.827088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:43.261745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:43.736693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:44.187844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:44.688223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:45.146230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:46.026211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:46.633362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:47.114577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:47.606790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:53.317003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:53.752716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:55.646284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:56.138865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:56.721974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:57.147804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:57.755037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:58.243298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:58.735258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:49:59.585762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:06.576228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:07.628744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:08.089922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:09.471764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:09.858228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:50:09.896342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:10.705070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:11.168326Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:50:11.312396Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:50:11.716478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:50:24.006647Z | Info | Live bytes: 709.40MB Heap size: 2984.25MB +2024-07-02T11:51:24.067671Z | Info | Live bytes: 709.40MB Heap size: 2984.25MB +2024-07-02T11:52:24.096936Z | Info | Live bytes: 706.00MB Heap size: 2984.25MB +2024-07-02T11:53:24.102007Z | Info | Live bytes: 706.00MB Heap size: 2984.25MB +2024-07-02T11:53:34.345626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:38.215680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:38.879503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:38.981851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:39.028659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:39.237027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:39.337543Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:39.673107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:39.728055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:40.101389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:40.132500Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:40.223540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:40.431233Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:40.510149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:40.593889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:40.605622Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:41.965283Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:42.227091Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:42.336206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:42.757114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:44.611911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:45.616418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:45.620694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:45.815493Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:45.857143Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:46.065304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:47.390359Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:47.750602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:48.669043Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:53:48.710059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:53:49.154787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:24.104116Z | Info | Live bytes: 722.20MB Heap size: 2984.25MB +2024-07-02T11:54:24.276063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:24.966641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:25.881602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:27.719894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:30.576551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:31.048635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:31.471354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:32.343340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:56.171494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:56.853164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:57.343818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:57.832205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:54:58.958759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:01.167391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:13.295315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:13.543753Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:13.667737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:13.722576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:13.901515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:14.025645Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:14.100989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:14.103900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:14.382994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:14.422113Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:14.520189Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:14.633963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:15.208376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:15.614604Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:15.752843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:15.760677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:15.905931Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:15.996965Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:55:16.283775Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:17.075219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:17.651429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:18.383334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:18.875972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:19.352274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:20.886591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:21.648235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:23.457618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:23.931311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:24.105664Z | Info | Live bytes: 743.08MB Heap size: 2984.25MB +2024-07-02T11:55:26.989225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:27.486730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:28.881899Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:55:29.060228Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:55:29.464192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:40.411871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:55:41.022415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:56:24.116926Z | Info | Live bytes: 856.56MB Heap size: 2984.25MB +2024-07-02T11:56:49.232848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:57:24.118265Z | Info | Live bytes: 869.74MB Heap size: 2984.25MB +2024-07-02T11:57:24.312377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:57:48.051875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:58:24.170871Z | Info | Live bytes: 880.99MB Heap size: 2984.25MB +2024-07-02T11:58:31.148788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:58:52.391152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:58:53.839493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:58:56.214473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:58:56.942549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:58:57.447974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:01.444845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:01.942126Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:59:01.957845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:02.603803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:59:02.679647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:03.123485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:03.551619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:03.965266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:04.980574Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:59:11.392413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:12.571780Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:59:16.447114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:16.989731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:23.265791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:24.173921Z | Info | Live bytes: 909.25MB Heap size: 2984.25MB +2024-07-02T11:59:24.881925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:25.308174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:26.425092Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:59:33.990804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:34.875007Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T11:59:38.009298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:38.519025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:47.871516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:47.979504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:59:48.350026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:48.764482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:49.384757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:49.895760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T11:59:49.985676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:50.422755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T11:59:50.687020Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:00:24.182274Z | Info | Live bytes: 1174.13MB Heap size: 2984.25MB +2024-07-02T12:00:40.257628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:40.410076Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:40.499343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:40.612029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:40.654165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:40.787277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:40.873381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:40.992487Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:41.149406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:41.523943Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:41.644740Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:41.712265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:41.884416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:42.743569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:42.773588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:43.555912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:43.980772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:44.164679Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:00:44.453054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:45.102470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:00:45.530437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:07.638709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:16.466793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:24.221343Z | Info | Live bytes: 1236.12MB Heap size: 2984.25MB +2024-07-02T12:01:26.846703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:42.425969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:42.800578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:01:43.149285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:49.307740Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:01:49.382847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:49.838660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:50.253553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:01:50.848264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:02:24.225800Z | Info | Live bytes: 657.50MB Heap size: 2984.25MB +2024-07-02T12:03:24.287139Z | Info | Live bytes: 657.50MB Heap size: 2984.25MB +2024-07-02T12:04:24.348234Z | Info | Live bytes: 657.50MB Heap size: 2984.25MB +2024-07-02T12:05:24.409964Z | Info | Live bytes: 657.50MB Heap size: 2984.25MB +2024-07-02T12:06:24.471389Z | Info | Live bytes: 657.50MB Heap size: 2984.25MB +2024-07-02T12:06:34.191515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:35.979514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:38.797143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:42.401391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:43.551766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:44.859711Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:44.995542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.132002Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.218341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:45.241299Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.400832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.516147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.633516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.722997Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.785439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:45.814514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:45.924486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:06:46.335071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:06:55.080338Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:07:14.652591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:07:24.479893Z | Info | Live bytes: 822.91MB Heap size: 2984.25MB +2024-07-02T12:08:04.808805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:05.508137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:06.067649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:06.573558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:07.032775Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:07.575944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:08.424406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:09.882116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:10.493751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:11.983042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:12.543710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:14.438814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:14.890931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:15.599665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:16.032304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:16.554906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:17.103410Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:17.609570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:24.488935Z | Info | Live bytes: 866.78MB Heap size: 2984.25MB +2024-07-02T12:08:28.000197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:28.463033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:31.986813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:37.907725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:38.410040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:39.182737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:39.814589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:39.936622Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:08:40.007415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:08:40.303567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:40.779259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:08:42.144708Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:08:42.327973Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:08:42.732729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:09:24.531478Z | Info | Live bytes: 944.63MB Heap size: 2984.25MB +2024-07-02T12:10:24.543027Z | Info | Live bytes: 944.63MB Heap size: 2984.25MB +2024-07-02T12:11:24.604749Z | Info | Live bytes: 949.35MB Heap size: 2984.25MB +2024-07-02T12:11:34.981510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:35.437891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:36.426774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:36.864346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:38.648775Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:42.135325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:42.172050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:42.782706Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:42.842628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:43.153025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:43.340740Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:43.451047Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:43.523990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:43.548094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:43.698503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:43.750519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:44.066684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:45.271459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:45.787309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:49.101196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:50.277549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:50.336364Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:50.636855Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:50.701460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:50.760746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:50.914273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:51.000023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:51.093036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:51.131069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:51.436164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:51.591071Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:51.802395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:52.239778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:53.402525Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:53.511945Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:53.595390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:54.376928Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:11:54.745233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:55.447711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:56.086536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:56.554853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:11:57.022233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:01.384836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:02.019798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:02.029424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:02.493382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:02.760087Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:02.950168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:03.121085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:03.288037Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:03.585848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:03.653334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:03.700320Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:03.773486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:03.842153Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:04.068181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:04.595254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:04.827647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:05.186514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:05.324533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:05.503724Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:05.695222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:06.738736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:08.567224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:09.544999Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:09.909241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:10.719886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:12.416666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:13.867704Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:13.909167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:14.487056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:14.942472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:15.901611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:16.389590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:17.798601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:19.026499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:19.218975Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:19.368060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:19.467963Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:19.591025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:19.694773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:19.731608Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:20.078355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:20.292165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:20.542397Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:20.657270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:20.671179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:20.729698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:20.905181Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:12:21.106729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:21.672151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:22.299483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:22.804636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:23.253749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:24.018336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:24.607529Z | Info | Live bytes: 645.17MB Heap size: 3057.65MB +2024-07-02T12:12:25.192328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:26.166843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:27.575076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:28.146813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:31.375208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:33.476233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:53.070188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:12:59.641754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:00.416404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:01.938678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:02.356637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:03.104569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:05.639571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:07.600828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:11.719825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:12.497737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:14.513316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:16.278021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:23.171222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:24.569568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:24.609504Z | Info | Live bytes: 962.71MB Heap size: 3057.65MB +2024-07-02T12:13:24.997557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:27.593991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:28.053439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:28.499511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:28.932925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:29.464389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:29.967452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:30.381843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:32.255493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:33.997578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:35.100912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:35.795597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:37.788017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:38.213993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:38.763249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:39.353117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:40.686751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:42.022286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:44.137419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:44.700625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:45.562985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:46.585640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:47.966347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:50.679080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:51.439875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:51.999215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:52.915195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:54.423483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:56.437105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:58.038105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:58.552552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:59.249600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:13:59.799792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:00.281409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:00.722367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:01.978133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:03.497466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:05.801033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:10.490573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:10.907496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:15.683486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:17.358291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:19.405777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:21.406346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:24.612776Z | Info | Live bytes: 1120.65MB Heap size: 3178.23MB +2024-07-02T12:14:39.575465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:42.087911Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:14:42.146313Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:14:42.551504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:58.167683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:58.850233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:59.060962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:14:59.271306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:59.348356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:14:59.491342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:14:59.648398Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:14:59.726519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:14:59.752194Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:14:59.852333Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:14:59.923236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:00.219361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:00.667844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:01.179321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:01.943024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:02.253720Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:02.317536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:02.410720Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:02.630945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:04.873740Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:15:08.800987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:17.837161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:21.308408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:24.613927Z | Info | Live bytes: 1126.48MB Heap size: 3356.49MB +2024-07-02T12:15:24.649862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:24.694892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:24.782723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:24.841247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:24.916818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:24.997292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:25.030115Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:15:25.223484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:25.758903Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:15:25.793041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:15:25.905842Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:15:26.289561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:00.529449Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:00.588455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:00.663064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:00.732795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:00.815880Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:00.913711Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:00.986116Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:01.116771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:01.749577Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:16:01.814312Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:16:01.857836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:04.733714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:04.877506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:05.058923Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:05.145787Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:05.195958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:05.426932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:05.536398Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:05.781469Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:05.900892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:05.934335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:06.134361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:06.337712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:06.480019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:06.536161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:06.645045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:06.783064Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:06.898435Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:07.043767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:07.062681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:07.146642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:07.220189Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:07.459179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:09.642855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:10.178014Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:10.656937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:10.990873Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:16:11.172908Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:16:11.578457Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:24.626662Z | Info | Live bytes: 654.72MB Heap size: 3356.49MB +2024-07-02T12:16:33.197943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:33.685152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:35.402048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:35.848699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:36.561294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:37.570251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:37.998170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:38.428983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:39.022484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:39.566617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:40.609710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:40.794618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:41.013756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:41.153331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:41.225890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:16:41.594764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:42.705153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:49.892151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:52.048508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:16:57.035795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:00.309338Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:03.174272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:03.595195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:05.809687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:06.265560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:12.365560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:20.870934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:24.160354Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:17:24.215695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:17:24.296846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:24.363785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:17:24.422939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:17:24.498952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:17:24.554483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:17:24.629772Z | Info | Live bytes: 1061.03MB Heap size: 3356.49MB +2024-07-02T12:17:24.741513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:25.703786Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:17:25.776590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:25.932960Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:17:26.323220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:31.832945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:32.254758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:32.746082Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:17:35.148824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:35.675590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:53.380669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:53.612730Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-02T12:17:59.453419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:17:59.899461Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:18:00.081746Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:18:00.484743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:18:04.694043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:18:05.845654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:18:06.329634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:18:09.472277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:18:09.930886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:18:24.643775Z | Info | Live bytes: 1208.89MB Heap size: 3356.49MB +2024-07-02T12:19:24.669951Z | Info | Live bytes: 1208.89MB Heap size: 3356.49MB +2024-07-02T12:20:20.875566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:21.366105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:22.650787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:24.671733Z | Info | Live bytes: 1208.15MB Heap size: 3356.49MB +2024-07-02T12:20:24.777478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:25.456924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:26.900345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:29.393232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:35.170867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:35.946906Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:20:36.134406Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:20:36.539346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:39.859825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:40.363487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:42.732881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:47.321262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:47.855281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:48.533566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:49.229753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:50.296293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:50.758302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:51.229976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:52.069418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:52.503199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:53.149561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:53.912014Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:20:59.589989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:01.826488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:03.003474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:04.725789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:06.185316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:09.314257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:10.021549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:12.637230Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:21:12.667610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:12.689958Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:21:13.095373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:24.684199Z | Info | Live bytes: 1154.28MB Heap size: 3356.49MB +2024-07-02T12:21:26.573744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:34.282434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:34.944034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:36.082206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:36.600944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:37.211999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:39.087349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:43.020752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:47.936237Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:48.014463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:48.080400Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:48.155870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:48.249957Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:48.311698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:48.466251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:49.331484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:49.638693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:49.761744Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:49.877191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:50.281656Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:50.441867Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:50.533335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:50.643725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:50.645683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:50.803554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:50.913876Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:51.020558Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:51.079250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:51.187312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:51.204225Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:51.648360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:51.693078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:51.819160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:51.902717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:52.091834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:52.371015Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:52.584260Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:52.718920Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:52.767199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:52.785287Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:52.919522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:52.930488Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:53.182211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:53.204943Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:53.289397Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:53.473160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:53.557742Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:53.606039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:53.655964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:53.781826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:54.053960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:54.058533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:54.272813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:54.383014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:21:54.473362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:21:54.758858Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:21:54.953298Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:21:55.345487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:06.632818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:07.107646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:07.183907Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-02T12:22:14.589744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:15.391974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:21.636650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:21.906486Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-02T12:22:24.685646Z | Info | Live bytes: 810.61MB Heap size: 3356.49MB +2024-07-02T12:22:28.324735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:29.832261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:30.260822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:30.781900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:31.993235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:34.638302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:36.759513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:37.340641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:37.521990Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:22:37.707922Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:22:38.111588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:41.895275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:43.807717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:45.224951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:46.116755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:48.393316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:49.991911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:22:51.064610Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:22:57.964557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:00.735923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:02.914609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:06.247121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:07.509022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:08.397548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:09.667896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:11.591732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:15.389642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:16.206220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:16.370053Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:23:24.694098Z | Info | Live bytes: 1571.28MB Heap size: 3356.49MB +2024-07-02T12:23:41.429774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:42.101562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:43.387130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:43.803828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:44.314873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:45.895348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:48.132979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:48.565613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:49.050433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:23:49.258623Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:24:01.490712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:02.011056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:02.622847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:03.165917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:03.685751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:07.999117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:08.682967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:09.236025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:09.733084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:10.293702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:11.081099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:11.916686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:24.707806Z | Info | Live bytes: 1083.94MB Heap size: 3356.49MB +2024-07-02T12:24:31.463936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:24:31.512420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:31.995519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:32.419785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:33.410223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:35.593205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:36.274469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:38.437542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:38.776789Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:24:42.430910Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:43.006623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:44.165505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:44.633708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:45.234359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:47.340324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:49.715062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:50.187874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:50.615632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:24:53.066857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:00.551709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:04.173947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:05.156831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:06.808959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:07.741059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:09.908189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:10.458320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:10.931376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:11.027718Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:25:13.770750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:14.272048Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:25:17.947578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:20.467566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:23.337519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:24.711394Z | Info | Live bytes: 1073.74MB Heap size: 3356.49MB +2024-07-02T12:25:25.031201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:26.812525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:27.871656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:28.370106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:28.974361Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:25:32.797857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:35.934542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:38.576815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:41.288573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:43.634777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:46.683840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:50.155526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:51.174120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:52.784786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:25:56.270322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:00.167808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:03.445814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:03.888163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:05.913262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:08.061935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:10.351743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:11.799473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:12.486559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:12.904762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:13.038418Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:26:24.504300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:24.712553Z | Info | Live bytes: 1087.08MB Heap size: 3356.49MB +2024-07-02T12:26:29.263881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:32.502142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:37.659431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:38.278502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:40.928235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:41.804801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:43.399966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:44.509716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:45.751183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:46.917090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:47.855628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:48.385967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:51.240185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:52.607055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:26:53.221282Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:27:02.119165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:27:02.563416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:27:03.246524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:27:03.731730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:27:24.717283Z | Info | Live bytes: 988.30MB Heap size: 3356.49MB +2024-07-02T12:28:24.778205Z | Info | Live bytes: 992.57MB Heap size: 3356.49MB +2024-07-02T12:29:24.789636Z | Info | Live bytes: 992.57MB Heap size: 3356.49MB +2024-07-02T12:30:24.823770Z | Info | Live bytes: 992.57MB Heap size: 3356.49MB +2024-07-02T12:31:24.836809Z | Info | Live bytes: 992.57MB Heap size: 3356.49MB +2024-07-02T12:31:52.543773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:31:53.075163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:32:02.709908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:32:24.859331Z | Info | Live bytes: 1094.83MB Heap size: 3356.49MB +2024-07-02T12:33:24.917966Z | Info | Live bytes: 1094.83MB Heap size: 3356.49MB +2024-07-02T12:33:48.437732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:33:49.131052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:33:55.540592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:33:56.078072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:00.047087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:00.708242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:01.607216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:02.280916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:02.978692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:03.726918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:04.560463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:05.626265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:24.938272Z | Info | Live bytes: 856.34MB Heap size: 3356.49MB +2024-07-02T12:34:34.673344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:35.227879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:36.916993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:37.377244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:34:37.742605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:37.997926Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:34:38.371561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:39.156183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:39.886299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:40.980991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:41.752772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:42.498384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:43.552902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:44.110468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:44.596524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:49.226997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:52.017482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:52.547438Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:34:52.643952Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:34:53.052671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:57.189454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:34:59.837040Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:35:24.962979Z | Info | Live bytes: 1375.35MB Heap size: 3356.49MB +2024-07-02T12:35:44.007199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:35:45.305943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:35:46.013160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:35:47.196884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:35:50.832474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:35:56.286407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:24.991645Z | Info | Live bytes: 829.12MB Heap size: 3356.49MB +2024-07-02T12:36:34.183300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:35.573362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:35.991332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:36.452801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:36.864943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:37.361598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:41.416219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:42.996883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:43.781899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:44.232735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:46.195066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:47.625108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:48.372845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:48.839816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:50.517476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:52.431170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:52.843146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:53.537884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:54.015478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:55.965647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:57.619945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:58.153303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:58.701563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:59.189809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:36:59.610296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:08.342737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:10.833207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:12.568671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:12.988566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:13.652601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:14.073045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:18.060625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:18.116800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:18.225814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:18.804067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:19.261498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:19.738719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:20.220311Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:20.247671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:22.869120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:23.424860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:23.882408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:24.351626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:24.876724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:24.992814Z | Info | Live bytes: 734.51MB Heap size: 3356.49MB +2024-07-02T12:37:25.797065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:26.805770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:26.972616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:27.500502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:30.756977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:33.646299Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:33.705563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:33.875618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:34.016311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:34.456619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:37:34.850593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:35.130871Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:37:35.328837Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:37:35.720730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:37:40.205552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:38:25.005543Z | Info | Live bytes: 933.50MB Heap size: 3356.49MB +2024-07-02T12:39:25.066785Z | Info | Live bytes: 933.50MB Heap size: 3356.49MB +2024-07-02T12:39:43.348940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:39:44.113057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:39:45.038337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:39:45.109958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:39:45.271539Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:39:45.470052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:39:45.475424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:39:47.235261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:06.618367Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:06.712618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:06.810179Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:06.941364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:07.138900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:07.226433Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:07.313912Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:07.513901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:08.117174Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:08.475012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:08.491195Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:08.662081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:08.763691Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:08.864590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:09.042089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:14.562989Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:14.923680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:17.814285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:18.735596Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:18.894539Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:18.981184Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:19.093395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:19.133486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:19.230950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:19.323680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:19.401193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:19.510790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:19.800103Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:19.921773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:20.167628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:20.237510Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:20.369395Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:20.533370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:20.583951Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:20.613493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:20.765007Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:20.867441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:40:21.145962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:25.070705Z | Info | Live bytes: 1385.93MB Heap size: 3356.49MB +2024-07-02T12:40:30.120148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:34.547690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:34.986350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:40:59.289989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:41:16.029021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:41:16.788191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:41:18.525874Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:41:18.873134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:41:21.035504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:41:25.073624Z | Info | Live bytes: 973.09MB Heap size: 3356.49MB +2024-07-02T12:41:31.425201Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:41:31.779681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:41:42.866837Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:41:43.196348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:41:44.345460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:42:05.698219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:42:05.769704Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:42:06.045336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:42:06.538486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:42:08.922826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:42:09.794231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:42:10.212034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:42:10.949449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:42:25.087007Z | Info | Live bytes: 1342.56MB Heap size: 3356.49MB +2024-07-02T12:43:00.229673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:02.293096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:03.038877Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:03.408569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:04.133659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:04.255897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:04.617689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:04.937436Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:43:05.128502Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:43:05.522936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:24.343403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:24.454574Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:24.522036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:24.629247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:24.705658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:24.755743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:25.098616Z | Info | Live bytes: 750.86MB Heap size: 3356.49MB +2024-07-02T12:43:25.141152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:25.148067Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:25.190957Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:25.396514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:25.543167Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:25.564747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:25.715679Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:25.825313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:26.086610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:26.149635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:26.193832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:26.375023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:26.479093Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:26.511847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:26.658198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:26.746862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:26.878562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:27.034920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:27.593723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:43:27.971792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:32.372600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:33.204197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:43:33.539658Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:44:25.113517Z | Info | Live bytes: 876.59MB Heap size: 3356.49MB +2024-07-02T12:45:08.741498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:45:09.737192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:45:14.534436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:45:20.057632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:45:25.119681Z | Info | Live bytes: 920.63MB Heap size: 3356.49MB +2024-07-02T12:46:25.162842Z | Info | Live bytes: 920.63MB Heap size: 3356.49MB +2024-07-02T12:47:25.224655Z | Info | Live bytes: 920.63MB Heap size: 3356.49MB +2024-07-02T12:47:31.012196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:41.202557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:46.048369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:52.503860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:53.012549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:53.707638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:54.395355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:56.318492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:56.933231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:47:57.622898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:25.252773Z | Info | Live bytes: 1228.42MB Heap size: 3356.49MB +2024-07-02T12:48:33.990385Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:48:34.069761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:48:34.215001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:48:34.320508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:35.151630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:38.610294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:39.102747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:39.433094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:48:39.534920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:40.204374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:40.702526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:41.213520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:41.721863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:42.164415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:42.716722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:43.211649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:46.234042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:48:48.200635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:49:01.710651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:49:02.071644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:49:02.863206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:49:10.354920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:49:10.785367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:49:25.263522Z | Info | Live bytes: 782.53MB Heap size: 3356.49MB +2024-07-02T12:50:25.269914Z | Info | Live bytes: 782.53MB Heap size: 3356.49MB +2024-07-02T12:51:25.331044Z | Info | Live bytes: 782.53MB Heap size: 3356.49MB +2024-07-02T12:52:25.392141Z | Info | Live bytes: 782.53MB Heap size: 3356.49MB +2024-07-02T12:53:18.090741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:18.563778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:19.181590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:53:19.538482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:20.036090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:20.656660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:21.290262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:21.792703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:25.395708Z | Info | Live bytes: 838.75MB Heap size: 3356.49MB +2024-07-02T12:53:27.307717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:28.235004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:30.354533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:32.657880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:33.826181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:53:52.288319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:15.765676Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:15.869671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:15.930765Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:15.996623Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:16.057915Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:16.103174Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:16.310554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:16.747777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:16.819298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:16.857762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:16.892315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:17.024578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:17.293219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:17.710558Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:17.926262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:18.071650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:18.109812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:18.208293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:18.290503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:18.386683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:18.571245Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:18.606596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:18.645295Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:19.039898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:19.221305Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ ] +2024-07-02T12:54:19.816595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:21.914892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:22.244071Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T12:54:22.301437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:25.397776Z | Info | Live bytes: 1252.86MB Heap size: 3356.49MB +2024-07-02T12:54:34.588411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:35.019390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:38.821257Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:38.917067Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:54:39.152347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:39.588328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:43.671054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:44.193892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:46.853906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:47.269687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:48.674103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:49.587799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:51.247836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:51.849510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:54:55.650167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:55:09.890726Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:55:10.362716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:55:10.381936Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-02T12:55:25.410262Z | Info | Live bytes: 1220.81MB Heap size: 3356.49MB +2024-07-02T12:56:25.471299Z | Info | Live bytes: 1220.81MB Heap size: 3356.49MB +2024-07-02T12:57:25.488172Z | Info | Live bytes: 1220.81MB Heap size: 3356.49MB +2024-07-02T12:58:18.893464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:23.668562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:25.490985Z | Info | Live bytes: 1221.82MB Heap size: 3356.49MB +2024-07-02T12:58:27.110788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:31.321471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:35.477150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:41.409556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:58:41.765403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:52.162586Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:58:52.452066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:53.009137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:54.388970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:55.240560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:56.320484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:56.974504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:58:57.903455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:06.096299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:08.014664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:08.604359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:10.572493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:11.622116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:19.421733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:20.342641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:21.155026Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs": [ ] +2024-07-02T12:59:25.495902Z | Info | Live bytes: 1235.11MB Heap size: 3356.49MB +2024-07-02T12:59:26.685887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:30.282243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:35.467624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:59:35.648353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:36.384509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:36.867984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:38.074411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:59:38.118763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:38.209165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:59:38.581129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:39.236589Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T12:59:39.605903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:56.079491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:56.580341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:57.174368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T12:59:58.069888Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs": [ ] +2024-07-02T13:00:05.841820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:00:08.628378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:00:10.541491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:00:11.214836Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs": [ ] +2024-07-02T13:00:25.500619Z | Info | Live bytes: 1251.34MB Heap size: 3356.49MB +2024-07-02T13:01:25.561840Z | Info | Live bytes: 1251.34MB Heap size: 3356.49MB +2024-07-02T13:01:26.253767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:01:28.275404Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:01:28.455003Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:01:28.861969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:01:39.445627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:01:55.654779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:01:56.127649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:01:57.328873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:01:58.403754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:00.623406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:00.899111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:02:01.085658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:01.663868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:02.150430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:02.399526Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:02:02.647713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:03.298713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:03.776176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:04.198884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:05.019840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:05.493206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:05.934523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:10.354671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:21.145340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:22.171269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:25.565756Z | Info | Live bytes: 890.31MB Heap size: 3356.49MB +2024-07-02T13:02:26.188390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:26.636641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:27.145402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:27.816678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:28.490787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:28.975861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:29.751155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:32.407413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:32.834617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:33.253779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:33.720782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:34.244552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:02:37.150634Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:33:56.620693Z | Info | Live bytes: 1087.00MB Heap size: 3356.49MB +2024-07-02T13:34:56.623876Z | Info | Live bytes: 1087.00MB Heap size: 3356.49MB +2024-07-02T13:35:42.601009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:35:54.366816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:35:56.639676Z | Info | Live bytes: 1105.66MB Heap size: 3356.49MB +2024-07-02T13:36:56.648133Z | Info | Live bytes: 1105.66MB Heap size: 3356.49MB +2024-07-02T13:37:56.651287Z | Info | Live bytes: 1105.66MB Heap size: 3356.49MB +2024-07-02T13:38:56.712962Z | Info | Live bytes: 1105.66MB Heap size: 3356.49MB +2024-07-02T13:39:56.768238Z | Info | Live bytes: 1105.66MB Heap size: 3356.49MB +2024-07-02T13:40:50.628226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:40:51.270514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:40:56.770297Z | Info | Live bytes: 1164.51MB Heap size: 3356.49MB +2024-07-02T13:40:58.985827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:00.138825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:00.663624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:01.496216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:01.932697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:11.800867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:12.520424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:22.685148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:23.170817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:24.240626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:24.687971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:29.707914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:30.666470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:37.784068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:38.260461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:39.040341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:39.463021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:39.708924Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:41:45.814267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:46.375206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:52.357755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:52.795453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:53.228614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:53.729739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:54.231447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:41:54.317660Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:41:56.772863Z | Info | Live bytes: 907.42MB Heap size: 3356.49MB +2024-07-02T13:41:58.541781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:00.289560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:09.309411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:33.331731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:36.664793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:38.055683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:38.470326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:41.811696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:45.425332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:49.881410Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:50.586791Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:42:50.650417Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:42:51.056695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:42:56.778682Z | Info | Live bytes: 1074.47MB Heap size: 3356.49MB +2024-07-02T13:43:51.524448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:43:56.780967Z | Info | Live bytes: 1112.53MB Heap size: 3356.49MB +2024-07-02T13:44:22.217594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:44:25.326486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:44:27.965185Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:44:29.958768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:44:30.038424Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:44:31.461719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:44:56.808467Z | Info | Live bytes: 1229.73MB Heap size: 3356.49MB +2024-07-02T13:45:04.775665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:45:19.303376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:45:20.884759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:45:56.836787Z | Info | Live bytes: 1231.34MB Heap size: 3356.49MB +2024-07-02T13:46:13.396532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:14.069519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:16.360687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:18.419916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:20.492040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:22.711449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:24.712992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:25.790792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:26.973669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:30.108959Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:46:35.420347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:38.434002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:39.822423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:40.617520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:43.076139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:43.748694Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs": [ ] +2024-07-02T13:46:48.896946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:51.387667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:52.379677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:52.787256Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs" ] +2024-07-02T13:46:56.176817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:46:56.838387Z | Info | Live bytes: 1450.57MB Heap size: 3356.49MB +2024-07-02T13:47:02.289656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:05.889759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:06.333208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:07.355776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:08.921229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:10.137324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:12.166419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:12.777990Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-02T13:47:17.330598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:18.050536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:18.593482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:21.671126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:23.294047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:24.816212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:26.758349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:29.379250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:47:56.866996Z | Info | Live bytes: 1535.10MB Heap size: 3356.49MB +2024-07-02T13:48:56.871832Z | Info | Live bytes: 1535.10MB Heap size: 3356.49MB +2024-07-02T13:49:33.214619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:49:33.978718Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-02T13:49:42.970874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:49:45.885484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:49:47.412530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:49:50.182441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:49:50.873875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:49:51.802235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:49:52.675330Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-02T13:49:56.877858Z | Info | Live bytes: 737.06MB Heap size: 3356.49MB +2024-07-02T13:49:59.167919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:02.051778Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-02T13:50:08.633665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:14.612430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:27.663042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:43.440982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:45.438142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:55.441268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:56.879660Z | Info | Live bytes: 821.53MB Heap size: 3356.49MB +2024-07-02T13:50:57.078433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:58.025946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:58.514567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:50:59.742705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:00.410174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:01.002755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:02.693992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:03.580835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:03.715119Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:51:03.990563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:51:04.075874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:08.654998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:09.246519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:51:09.596180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:11.479575Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-02T13:51:44.846339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:46.040318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:46.729530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:47.255944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:49.084175Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-02T13:51:50.727084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:51:56.889063Z | Info | Live bytes: 997.61MB Heap size: 3356.49MB +2024-07-02T13:52:56.950565Z | Info | Live bytes: 997.61MB Heap size: 3356.49MB +2024-07-02T13:53:57.011845Z | Info | Live bytes: 997.61MB Heap size: 3356.49MB +2024-07-02T13:54:41.429640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:54:43.712347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:54:45.356568Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Expr.hs": [ ] +2024-07-02T13:54:57.024482Z | Info | Live bytes: 1063.56MB Heap size: 3356.49MB +2024-07-02T13:55:14.721818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:30.326569Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/Types.hs +2024-07-02T13:55:30.327225Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-02T13:55:30.439798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:35.612625Z | Info | Load cabal cradle using single file +2024-07-02T13:55:36.593504Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT96586-334 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-02T13:55:37.823750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:40.297712Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-648e747809904bf8a445e4ab5be3a6d6f62ad1c0 +2024-07-02T13:55:40.298692Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-648e747809904bf8a445e4ab5be3a6d6f62ad1c0 +2024-07-02T13:55:40.308766Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-02T13:55:40.439771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:41.046988Z | Warning | codeRange: no HieAst exist for file +2024-07-02T13:55:44.998326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:45.827336Z | Warning | codeRange: no HieAst exist for file +2024-07-02T13:55:46.024593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:49.287539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:51.252368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:51.713631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:53.579826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:55:57.031842Z | Info | Live bytes: 1054.19MB Heap size: 3428.84MB +2024-07-02T13:55:59.897610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:03.387481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:03.492353Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:03.819137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:03.847294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:03.989586Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:04.230921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:04.499957Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:04.716159Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:04.741325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:04.833765Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:05.215350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:06.307773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:06.452642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:06.537912Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:06.686290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:06.704592Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:06.743611Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:06.810683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:06.842465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:07.056750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:07.129221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:07.369421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:07.606651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:07.703867Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:07.749089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:08.031487Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:08.412080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:08.956574Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:09.340183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:09.526905Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:09.911715Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:10.414293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:10.493764Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:10.579992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:10.791974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:10.803458Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:11.901845Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:12.107187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:12.179036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:12.281173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:12.521351Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:12.895050Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:12.912409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:13.049770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:13.163188Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:13.250075Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:13.430905Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:13.431299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:14.274953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:14.805224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:14.887755Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:14.973962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:15.017906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:15.116325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:15.180744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:15.834060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:16.312203Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:20.817055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:23.712754Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:23.752157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:23.914143Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:23.978499Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:24.057567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:24.059632Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:24.110165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-02T13:56:24.488168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:24.822375Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:56:24.991564Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:56:25.389232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:26.297107Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:56:26.441080Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:56:26.566619Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:56:26.701222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T13:56:26.946283Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:56:26.946366Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/ShelleyBased/Query.hs" ] +2024-07-02T13:56:57.061911Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T13:57:57.065617Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T13:58:57.126954Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T13:59:57.188816Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T14:00:57.234597Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T14:01:57.294353Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T14:02:57.354239Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T14:03:57.392260Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T14:04:57.452241Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T14:05:57.498375Z | Info | Live bytes: 1374.22MB Heap size: 3428.84MB +2024-07-02T14:06:31.231640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T14:06:32.351833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T14:06:38.706819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T14:06:57.520532Z | Info | Live bytes: 1394.62MB Heap size: 3428.84MB +2024-07-02T14:07:33.983309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T14:07:35.271792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T14:07:57.535252Z | Info | Live bytes: 1394.62MB Heap size: 3428.84MB +2024-07-02T14:08:10.700890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T14:08:30.033835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T14:08:57.561339Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:09:57.621336Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:10:57.641727Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:11:57.677343Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:12:57.686343Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:13:57.746339Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:14:57.788913Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:15:57.822765Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:16:57.882295Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:17:57.942754Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:18:58.001641Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:19:58.061279Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:20:58.121943Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:21:58.182426Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:22:58.242353Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:23:58.302813Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:24:58.363390Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:25:58.400759Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:26:58.460240Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:27:58.469814Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:28:58.530219Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:29:58.590234Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:30:58.600482Z | Info | Live bytes: 1389.27MB Heap size: 3428.84MB +2024-07-02T14:31:55.192451Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/Types.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/New/EraIndependent/Expr.hs" ] +2024-07-02T14:31:55.272820Z | Info | LSP: received shutdown +2024-07-02T14:31:55.274977Z | Error | Got EOF +2024-07-02 17:16:31.6190000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-02 17:16:31.6200000 [client] INFO Finding haskell-language-server +2024-07-02 17:16:31.6210000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:31.6210000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:31.6280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-02 17:16:31.7650000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:31.7650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:31.7710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-02 17:16:31.9080000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:31.9090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:31.9140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-02 17:16:32.1200000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:32.1200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:32.1270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-02 17:16:32.2980000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:32.2980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:32.3020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-02 17:16:32.3160000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:32.3160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:32.3210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-02 17:16:32.3440000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:32.3440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:32.3490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-02 17:16:32.3680000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-02 17:16:32.4810000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:32.4810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:32.4870000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-02 17:16:32.6140000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-02 17:16:32.6140000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-02 17:16:39.2800000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-02 17:16:39.3410000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-02 17:16:39.3410000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:39.3410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:39.3480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-02 17:16:39.4230000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:39.4230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:39.4280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-02 17:16:39.4440000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:39.4440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:39.4480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-02 17:16:39.4620000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:39.4620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:39.4680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-02 17:16:39.4830000 [client] INFO Checking for ghcup installation +2024-07-02 17:16:39.4830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-02 17:16:39.4890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-02 17:16:39.5850000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-02 17:16:39.5850000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-02 17:16:39.5850000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-02 17:16:39.5850000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-02 17:16:39.5850000 [client] INFO server environment variables: +2024-07-02 17:16:39.5850000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-02 17:16:39.5850000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-02 17:16:39.5850000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-02 17:16:39.5860000 [client] INFO Starting language server +2024-07-02T17:16:49.436067Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-02T17:16:49.437160Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-02T17:16:49.437367Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-02T17:16:49.441273Z | Info | Logging heap statistics every 60.00s +2024-07-02T17:16:49.449261Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-02T17:16:49.449863Z | Info | Starting server +2024-07-02T17:16:49.451611Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-02T17:16:49.481108Z | Info | Started LSP server in 0.03s +2024-07-02T17:16:50.799698Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query/New/AnyEra/Query.hs +2024-07-02T17:16:50.800713Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-02T17:16:51.306986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T17:16:51.307061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T17:16:52.296418Z | Info | Load cabal cradle using single file +2024-07-02T17:16:52.768118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T17:16:53.301433Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT284767-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-02T17:16:56.613628Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-648e747809904bf8a445e4ab5be3a6d6f62ad1c0 +2024-07-02T17:16:56.618808Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-02T17:16:58.430477Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/DRepMetadata.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-02T17:17:02.847325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T17:17:49.486597Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:18:49.547363Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:19:29.088718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-02T17:19:49.552127Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:20:49.612216Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:21:49.657001Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:22:49.701071Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:23:49.703103Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:24:49.730052Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:25:49.791161Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:26:49.825969Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:27:49.830373Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:28:49.875674Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:29:49.913906Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:30:49.974834Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:31:50.018536Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:32:50.023073Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:33:50.083312Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:34:50.143284Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:35:50.203941Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:36:50.242304Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:37:50.243181Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:38:50.246204Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:39:50.306523Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:40:50.367548Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:41:50.427343Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:42:50.488320Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:43:50.549128Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:44:50.557320Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:45:50.618042Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:46:50.678842Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:47:50.739396Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:48:50.786168Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:49:50.787562Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:50:50.847364Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:51:50.908058Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:52:50.917107Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:53:50.927559Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:54:50.988620Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:55:50.989780Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:56:51.050490Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:57:51.111350Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:58:51.171247Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T17:59:51.231757Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:00:51.237242Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:01:51.297741Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:02:51.317267Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:03:51.377948Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:04:51.392286Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:05:51.452258Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:06:51.509765Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:07:51.515520Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:08:51.576180Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:09:51.614002Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:10:51.674387Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:11:51.695651Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:12:51.756945Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:13:51.765577Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:14:51.826916Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:15:51.883452Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:16:51.944635Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:17:52.005718Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:18:52.066295Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:19:52.127138Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:20:52.188429Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:21:52.249681Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:22:52.270341Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:23:52.331424Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:24:52.391285Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:25:52.451752Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:26:52.458064Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:27:52.471295Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:28:52.532277Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:29:52.553931Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:30:52.615296Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:31:52.676068Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:32:52.721881Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:33:52.782260Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:34:52.842281Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:35:52.902257Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:36:52.917558Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:37:52.959406Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:38:53.020654Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:39:53.081675Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:40:53.142707Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:41:53.203404Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:42:53.262499Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:43:53.323399Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:44:53.357497Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:45:53.418631Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:46:53.469017Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:47:53.525603Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:48:53.586925Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:49:53.606258Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:50:53.667050Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:51:53.728097Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:52:53.788950Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:53:53.792323Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:54:53.853054Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:55:53.861674Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:56:53.922931Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:57:53.951616Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:58:54.005668Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T18:59:54.032593Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:00:54.093848Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:01:54.155200Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:02:54.216378Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:03:54.258721Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:04:54.309404Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:05:54.357613Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:06:54.418870Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:07:54.479973Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:08:54.482208Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:09:54.501625Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:10:54.503010Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:11:54.529982Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:12:54.541639Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:13:54.602299Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:14:54.604770Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:15:54.664469Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:16:54.708981Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:17:54.723104Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:18:54.774699Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:19:54.782557Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:20:54.812421Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:21:54.851232Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:22:54.912292Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:23:54.942390Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:24:54.966323Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:25:54.997736Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:26:55.059057Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:27:55.081202Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:28:55.142330Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:29:55.203518Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:30:55.264797Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:31:55.290478Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:32:55.351457Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:33:55.412398Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:34:55.459417Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:35:55.520462Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:36:55.572044Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:37:55.632745Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:38:55.694108Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:39:55.724267Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:40:55.785550Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:41:55.837629Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:42:55.877114Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:43:55.938350Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:44:55.989672Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:45:56.050938Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:46:56.108427Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:47:56.149545Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:48:56.181550Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:49:56.218732Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:50:56.220244Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:51:56.281338Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:52:56.309540Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:53:56.346240Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:54:56.352575Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:55:56.354283Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:56:56.404756Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:57:56.410396Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:58:56.471259Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T19:59:56.488597Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:00:56.550046Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:01:56.576628Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:02:56.581461Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:03:56.593780Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:04:56.654839Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:05:56.716430Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:06:56.749572Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:07:56.808110Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:08:56.864268Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:09:56.892392Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:10:56.916947Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:11:56.966214Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:12:57.027473Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:13:57.065621Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:14:57.077659Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:15:57.139045Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:16:57.200416Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:17:57.249323Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:18:57.266297Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:19:57.301566Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:20:57.333637Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:21:57.378885Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:22:57.439395Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:23:57.500266Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:24:57.557581Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:25:57.618413Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:26:57.679239Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:27:57.736721Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:28:57.740370Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:29:57.800357Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:30:57.805597Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:31:57.813608Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:32:57.874975Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:33:57.936674Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:34:57.997643Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:35:58.058742Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:36:58.120249Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:37:58.181613Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:38:58.243225Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:39:58.304803Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:40:58.365262Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:41:58.425371Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:42:58.443134Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:43:58.462378Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:44:58.523199Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:45:58.581689Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:46:58.613800Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:47:58.674422Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:48:58.735305Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:49:58.796433Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:50:58.856454Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:51:58.890588Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:52:58.951498Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:53:59.005230Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:54:59.053297Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:55:59.071273Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:56:59.132297Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:57:59.140940Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:58:59.201467Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T20:59:59.229349Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:00:59.242248Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:01:59.304049Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:02:59.366018Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:03:59.427880Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:04:59.489515Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:05:59.550595Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:06:59.611842Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:07:59.644910Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:08:59.654501Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:09:59.714386Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:10:59.765672Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:11:59.826403Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:12:59.887423Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:13:59.948632Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:15:00.009879Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:16:00.070815Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:17:00.085360Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:18:00.146031Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:19:00.207388Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:20:00.268737Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:21:00.330242Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:22:00.391537Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:23:00.446952Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:24:00.499546Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:25:00.560983Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:26:00.622342Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:27:00.683654Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:28:00.693576Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:29:00.754865Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:30:00.810884Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:31:00.872305Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:32:00.896607Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:33:00.957224Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:34:00.977025Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:35:01.002779Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:36:01.063322Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:37:01.123829Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:38:01.141517Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:39:01.202335Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:40:01.244284Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:41:01.291033Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:42:01.352066Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:43:01.413106Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:44:01.421508Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:45:01.482536Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:46:01.543589Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:47:01.604846Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:48:01.666100Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:49:01.727338Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:50:01.781585Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:51:01.842899Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:52:01.904267Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:53:01.965453Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:54:02.026684Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:55:02.087998Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:56:02.149306Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:57:02.210462Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:58:02.229555Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T21:59:02.290687Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T22:00:02.351750Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T22:01:02.412467Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T22:02:02.419970Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T22:03:02.481138Z | Info | Live bytes: 518.64MB Heap size: 1722.81MB +2024-07-02T22:04:02.392288Z | Error | Got EOF +2024-07-03 07:36:54.4100000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-03 07:36:54.4120000 [client] INFO Finding haskell-language-server +2024-07-03 07:36:54.4140000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:54.4140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:54.4250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-03 07:36:54.9690000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:54.9690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:54.9830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 07:36:55.2260000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:55.2270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:55.2330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-03 07:36:55.4710000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:55.4710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:55.4770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-03 07:36:55.6900000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:55.6910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:55.6980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 07:36:55.7140000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:55.7140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:55.7220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-03 07:36:55.7380000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:55.7390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:55.7460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-03 07:36:55.7690000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-03 07:36:55.8690000 [client] INFO Checking for ghcup installation +2024-07-03 07:36:55.8700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:36:55.8750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-03 07:36:56.1020000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-03 07:36:56.1030000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-03 07:37:06.6040000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-03 07:37:06.6880000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-03 07:37:06.6880000 [client] INFO Checking for ghcup installation +2024-07-03 07:37:06.6880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:37:06.6930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 07:37:06.7880000 [client] INFO Checking for ghcup installation +2024-07-03 07:37:06.7880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:37:06.7920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-03 07:37:06.8080000 [client] INFO Checking for ghcup installation +2024-07-03 07:37:06.8080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:37:06.8130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 07:37:06.8270000 [client] INFO Checking for ghcup installation +2024-07-03 07:37:06.8270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:37:06.8310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-03 07:37:06.8450000 [client] INFO Checking for ghcup installation +2024-07-03 07:37:06.8450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 07:37:06.8490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-03 07:37:06.9430000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-03 07:37:06.9440000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 07:37:06.9440000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 07:37:06.9440000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03 07:37:06.9440000 [client] INFO server environment variables: +2024-07-03 07:37:06.9440000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-03 07:37:06.9440000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-03 07:37:06.9440000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-03 07:37:06.9450000 [client] INFO Starting language server +2024-07-03T07:37:19.995808Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-03T07:37:19.996869Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03T07:37:19.997141Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T07:37:20.001466Z | Info | Logging heap statistics every 60.00s +2024-07-03T07:37:20.012617Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T07:37:20.013284Z | Info | Starting server +2024-07-03T07:37:20.015738Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-03T07:37:20.166606Z | Info | Started LSP server in 0.15s +2024-07-03T07:37:21.905831Z | Info | Cradle path: cardano-api/internal/Cardano/Api/InMode.hs +2024-07-03T07:37:21.907007Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-03T07:37:22.491683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T07:37:22.492379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T07:37:24.584036Z | Info | Load cabal cradle using single file +2024-07-03T07:37:25.969730Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT7264-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-03T07:37:31.180680Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-648e747809904bf8a445e4ab5be3a6d6f62ad1c0 +2024-07-03T07:37:31.188513Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-03T07:38:20.036926Z | Info | Live bytes: 333.54MB Heap size: 1492.12MB +2024-07-03T07:39:20.053741Z | Info | Live bytes: 333.54MB Heap size: 1492.12MB +2024-07-03T07:39:21.387409Z | Info | LSP: received shutdown +2024-07-03T07:39:21.389215Z | Error | Got EOF +2024-07-03 08:04:22.7140000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-03 08:04:22.7150000 [client] INFO Finding haskell-language-server +2024-07-03 08:04:22.7160000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:22.7160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:22.7230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-03 08:04:23.1800000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:23.1800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:23.1850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 08:04:23.3610000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:23.3620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:23.3670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-03 08:04:23.4840000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:23.4840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:23.4900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-03 08:04:23.6070000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:23.6070000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:23.6120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 08:04:23.6290000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:23.6290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:23.6360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-03 08:04:23.6590000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:23.6590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:23.6640000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-03 08:04:23.6820000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-03 08:04:23.7200000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:23.7200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:23.7250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-03 08:04:23.8290000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-03 08:04:23.8300000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-03 08:04:33.5590000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-03 08:04:33.6360000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-03 08:04:33.6360000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:33.6360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:33.6440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 08:04:33.7180000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:33.7190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:33.7230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-03 08:04:33.7390000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:33.7390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:33.7430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 08:04:33.7570000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:33.7570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:33.7610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-03 08:04:33.7750000 [client] INFO Checking for ghcup installation +2024-07-03 08:04:33.7750000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:04:33.7790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-03 08:04:33.8640000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-03 08:04:33.8640000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 08:04:33.8640000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 08:04:33.8640000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03 08:04:33.8640000 [client] INFO server environment variables: +2024-07-03 08:04:33.8640000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-03 08:04:33.8640000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-03 08:04:33.8640000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-03 08:04:33.8650000 [client] INFO Starting language server +2024-07-03T08:04:42.821814Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-03T08:04:42.822865Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03T08:04:42.823154Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T08:04:42.825350Z | Info | Logging heap statistics every 60.00s +2024-07-03T08:04:42.831819Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T08:04:42.832176Z | Info | Starting server +2024-07-03T08:04:42.833766Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-03T08:04:42.861794Z | Info | Started LSP server in 0.03s +2024-07-03T08:04:44.015946Z | Info | LSP: received shutdown +2024-07-03T08:04:44.016746Z | Info | Reactor thread stopped +2024-07-03T08:04:44.025265Z | Error | Got EOF +2024-07-03 08:58:16.3650000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-03 08:58:16.3660000 [client] INFO Finding haskell-language-server +2024-07-03 08:58:16.3680000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:16.3680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:16.3740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-03 08:58:16.7800000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:16.7800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:16.7860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 08:58:16.9020000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:16.9020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:16.9070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-03 08:58:17.0230000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:17.0240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:17.0280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-03 08:58:17.1560000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:17.1560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:17.1600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 08:58:17.1730000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:17.1740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:17.1790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-03 08:58:17.1930000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:17.1930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:17.1980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-03 08:58:17.2190000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-03 08:58:17.2560000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:17.2560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:17.2600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-03 08:58:17.3550000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-03 08:58:17.3560000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-03 08:58:33.0400000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-03 08:58:33.2610000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-03 08:58:33.2610000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:33.2610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:33.2680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 08:58:33.3440000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:33.3440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:33.3470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-03 08:58:33.3630000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:33.3630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:33.3660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 08:58:33.3790000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:33.3790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:33.3830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-03 08:58:33.3980000 [client] INFO Checking for ghcup installation +2024-07-03 08:58:33.3980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 08:58:33.4030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-03 08:58:33.4870000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-03 08:58:33.4880000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 08:58:33.4880000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 08:58:33.4880000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03 08:58:33.4880000 [client] INFO server environment variables: +2024-07-03 08:58:33.4880000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-03 08:58:33.4880000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-03 08:58:33.4880000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-03 08:58:33.4890000 [client] INFO Starting language server +2024-07-03T08:58:42.461748Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-03T08:58:42.462755Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03T08:58:42.463151Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T08:58:42.467989Z | Info | Logging heap statistics every 60.00s +2024-07-03T08:58:42.478356Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T08:58:42.478776Z | Info | Starting server +2024-07-03T08:58:42.480543Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-03T08:58:42.607027Z | Info | Started LSP server in 0.13s +2024-07-03T08:58:43.889920Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-03T08:58:43.890688Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-03T08:58:44.463790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T08:58:45.301612Z | Info | Load cabal cradle using single file +2024-07-03T08:58:46.195331Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT158492-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-03T08:58:52.731501Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-914364913aa32f3c16b7cecf47a795d21f367459 +2024-07-03T08:58:52.738248Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-03T08:59:42.508120Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:00:42.567982Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:01:42.629181Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:02:42.671357Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:03:42.732469Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:04:42.776013Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:05:42.801571Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:06:42.861782Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:07:42.871921Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:08:42.922996Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:09:42.984208Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:10:43.045613Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:11:43.106672Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:12:43.167697Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:13:43.228533Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:14:43.282989Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:15:43.343863Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:16:43.405367Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:17:43.460277Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:18:43.467235Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:19:43.527793Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:20:43.588899Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:21:43.650443Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:22:43.711464Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:23:43.743866Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:57:11.937895Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:58:11.960468Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T09:59:12.021560Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:00:12.082374Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:01:12.143137Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:02:12.154282Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:03:12.214222Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:04:12.220201Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:05:12.280199Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:06:12.340274Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:07:12.400302Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:08:12.460866Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:09:12.521257Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:10:12.581252Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:11:12.641218Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:12:12.652694Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:13:12.713162Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:14:12.773145Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:15:12.833394Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:16:12.846537Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:17:12.907187Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:18:12.920303Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:19:12.939174Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:20:12.999265Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:21:13.058532Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:22:13.119169Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:23:13.179736Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:24:13.240140Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:25:13.244351Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:26:13.304210Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:27:13.334288Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:28:13.394993Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:29:13.455347Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:30:13.516031Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:31:13.576213Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:32:13.636928Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:33:13.697278Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:34:13.758033Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:35:13.818715Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:36:13.830209Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:37:13.889021Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:38:13.949143Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:39:13.955337Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:40:14.016539Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:41:14.077752Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:42:14.139443Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:43:14.141189Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:44:14.202087Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:45:14.263060Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:46:14.324623Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:47:14.385433Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:48:14.438574Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:49:14.499183Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:50:14.559336Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:51:14.619242Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:52:14.679400Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:53:14.739214Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:54:14.758776Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:55:14.812603Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:56:14.840705Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:57:14.872451Z | Info | Live bytes: 770.50MB Heap size: 1935.67MB +2024-07-03T10:58:14.888703Z | Info | Live bytes: 789.31MB Heap size: 1936.72MB +2024-07-03T10:59:14.892468Z | Info | Live bytes: 789.31MB Heap size: 1936.72MB +2024-07-03T11:00:14.953408Z | Info | Live bytes: 789.31MB Heap size: 1936.72MB +2024-07-03T11:01:15.014919Z | Info | Live bytes: 789.31MB Heap size: 1936.72MB +2024-07-03T11:02:15.076383Z | Info | Live bytes: 538.94MB Heap size: 2304.77MB +2024-07-03T11:03:15.099683Z | Info | Live bytes: 541.81MB Heap size: 2304.77MB +2024-07-03T11:04:15.160916Z | Info | Live bytes: 541.81MB Heap size: 2304.77MB +2024-07-03T11:05:15.221824Z | Info | Live bytes: 541.81MB Heap size: 2304.77MB +2024-07-03T11:06:15.283151Z | Info | Live bytes: 541.81MB Heap size: 2304.77MB +2024-07-03T11:06:20.726367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:06:26.569269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:06:27.162952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:06:30.017726Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Value.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/StakePoolMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Address.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/DRepMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-07-03T11:06:38.039616Z | Info | LSP: received shutdown +2024-07-03T11:06:38.041174Z | Error | Got EOF +2024-07-03T11:07:39.547674Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-03T11:07:39.548658Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03T11:07:39.548917Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T11:07:39.551603Z | Info | Logging heap statistics every 60.00s +2024-07-03T11:07:39.558439Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T11:07:39.558810Z | Info | Starting server +2024-07-03T11:07:39.560102Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-03T11:07:39.633612Z | Info | Started LSP server in 0.08s +2024-07-03T11:07:40.855544Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-03T11:07:40.856562Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-03T11:07:41.430403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:07:42.208613Z | Info | Load cabal cradle using single file +2024-07-03T11:07:43.083401Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT242632-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-03T11:07:46.180038Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-914364913aa32f3c16b7cecf47a795d21f367459 +2024-07-03T11:07:46.185008Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-03T11:08:36.451920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:08:37.058286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:08:38.051338Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:08:39.496468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:08:39.556236Z | Info | Live bytes: 640.04MB Heap size: 2322.60MB +2024-07-03T11:09:04.689871Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-03T11:09:08.973412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-03T11:09:09.243137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:09.357992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-03T11:09:09.852736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:11.426326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:11.565267Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-03T11:09:17.702160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:18.568283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:19.662808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:21.347769Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-03T11:09:21.537486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-03T11:09:21.847556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:24.431220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:24.581395Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-03T11:09:36.647103Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-03T11:09:36.729189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:37.058837Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-03T11:09:37.566857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:38.397004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:09:39.557708Z | Info | Live bytes: 996.05MB Heap size: 2662.33MB +2024-07-03T11:09:39.761707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:10:30.333251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:10:39.565584Z | Info | Live bytes: 592.66MB Heap size: 2669.67MB +2024-07-03T11:10:58.283624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T11:11:39.576657Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:12:39.638341Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:13:39.699810Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:14:39.745143Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:15:39.806411Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:16:39.817729Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:17:39.823810Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:18:39.848562Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:19:39.909869Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:20:39.950688Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:21:39.960475Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:22:39.992540Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:23:40.024534Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:24:40.060258Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:25:40.099890Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:26:40.120622Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:27:40.155035Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:28:40.168600Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:29:40.222010Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:30:40.254529Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:31:40.280586Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:32:40.312596Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:33:40.373904Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:34:40.376589Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:35:40.436605Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:36:40.497826Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:37:40.558880Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:38:40.568617Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:39:40.629918Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:40:40.653217Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:41:40.714385Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:42:40.760598Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:43:40.792523Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:44:40.824606Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:45:40.884602Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:46:40.888529Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:47:40.920625Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:48:40.973260Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:49:41.034476Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:50:41.095350Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:51:41.119908Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:52:41.181255Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:53:41.219717Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:54:41.280867Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:55:41.341584Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:56:41.402947Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:57:41.463267Z | Info | Live bytes: 615.98MB Heap size: 2669.67MB +2024-07-03T11:58:09.477964Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-03T11:58:41.491324Z | Info | Live bytes: 713.70MB Heap size: 2669.67MB +2024-07-03T11:59:41.499949Z | Info | Live bytes: 713.70MB Heap size: 2669.67MB +2024-07-03T12:00:41.560357Z | Info | Live bytes: 713.70MB Heap size: 2669.67MB +2024-07-03T12:01:22.111708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T12:01:41.564210Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:02:41.575048Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:03:41.635573Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:04:41.690465Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:05:41.751568Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:06:41.756234Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:07:41.817196Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:08:41.878411Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:09:41.939719Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:10:42.001119Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:11:42.062468Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:12:42.123958Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:13:42.185710Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:14:42.232497Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:15:42.293712Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:16:42.354993Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:17:42.416765Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:18:42.424662Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:19:42.476718Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:20:42.531031Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:21:42.592150Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:22:42.653474Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:23:42.714807Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:24:42.759507Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:25:42.770522Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:26:42.821267Z | Info | Live bytes: 754.44MB Heap size: 2669.67MB +2024-07-03T12:27:06.565961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T12:27:19.049386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T12:27:37.508380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T12:27:42.825709Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:28:42.885758Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:29:42.891611Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:30:42.952630Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:31:42.978273Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:32:43.017331Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:33:43.077247Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:34:43.138202Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:35:43.139492Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:36:43.201009Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:37:43.262314Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:38:43.304581Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:39:43.336577Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:40:43.344595Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:41:43.405913Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:42:43.467201Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:43:43.495733Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:44:43.556286Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:45:43.593233Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:46:43.653342Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:47:43.713337Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:48:43.764167Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:49:43.824841Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:50:43.885897Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:51:43.911578Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:52:43.972187Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:53:44.030781Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:54:44.091507Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:55:44.099457Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:56:44.160122Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:57:44.220398Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:58:44.281258Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T12:59:44.304762Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:00:44.365557Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:01:44.376364Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:02:44.437378Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:03:44.485859Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:04:44.546537Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:05:44.577754Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:06:44.638353Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:07:44.686707Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:08:44.699853Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:09:44.760667Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:10:44.821593Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:11:44.845902Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:12:44.856408Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:13:44.892106Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:14:44.941120Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:15:44.949182Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:16:45.010237Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:17:45.070205Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:18:45.130278Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:19:45.191132Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:20:45.251380Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:21:45.312286Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:22:45.373367Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:23:45.384426Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:24:45.445448Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:25:45.464509Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:26:45.525593Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:27:45.586874Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:28:45.648033Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:29:45.709186Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:30:45.724456Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:31:45.785661Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:32:45.846891Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:33:45.908187Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:34:45.953288Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:35:46.014480Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:36:46.072542Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:37:46.133772Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:38:46.194838Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:39:46.255717Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:40:46.316256Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:41:46.376793Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:42:46.384507Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:43:46.416567Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:44:46.418715Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:45:46.440693Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:46:46.481423Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:47:46.525010Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:48:46.585992Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:49:46.647011Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:50:46.708172Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:51:46.763226Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:52:46.824143Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:53:46.884209Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:54:46.944322Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:55:47.004265Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:56:47.064384Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:57:47.124930Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:58:47.185562Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T13:59:47.192865Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:00:47.200435Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:01:47.253375Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:02:47.285141Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:03:47.294236Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:04:47.352452Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:05:47.406937Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:06:47.467681Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:07:47.492540Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:08:47.509643Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:09:47.512528Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:10:47.573623Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:11:47.603978Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:12:47.615035Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:13:47.675492Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:14:47.708741Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:15:47.769979Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:16:47.831251Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:17:47.892751Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:18:47.953448Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:19:48.014509Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:20:48.075608Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:21:48.136524Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:22:48.197510Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:23:48.258295Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:24:48.298349Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:25:48.359334Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:26:48.404681Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:27:48.464329Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:28:48.524956Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:29:48.562551Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:30:48.563385Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:31:48.623833Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:32:48.684258Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:33:48.744230Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:34:48.804234Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:35:48.864306Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:36:48.924921Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:37:48.985337Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:38:49.045325Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:39:49.105321Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:40:49.165308Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:41:49.202637Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:42:49.262367Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:43:49.322186Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:44:49.324680Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:45:49.384290Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:46:49.444817Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:47:49.505259Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:48:49.565802Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:49:49.585107Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:50:49.645218Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:51:49.705198Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:52:49.765398Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:53:49.805261Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:54:49.865181Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:55:49.925231Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:56:49.985311Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:57:50.023314Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:58:50.029614Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T14:59:50.089273Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:00:50.149290Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:01:50.209334Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:02:50.215474Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:03:50.276152Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:04:50.336199Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:05:50.396491Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:06:50.456313Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:07:50.516252Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:08:50.577185Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:09:50.637295Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:10:50.698186Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:11:50.758436Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:12:50.776215Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:13:50.836644Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:14:50.860161Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:15:50.866858Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:16:50.871305Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:17:50.919568Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:18:50.927027Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:19:50.987967Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:20:51.048298Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:21:51.076768Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:22:51.130386Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:23:51.191225Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:24:51.251173Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:25:51.282790Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:26:51.317700Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:27:51.378604Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:28:51.440293Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:29:51.501849Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:30:51.563034Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:31:51.624529Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:32:51.686547Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:33:51.726231Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:34:51.787774Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:35:51.849256Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:36:51.896580Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:37:51.958145Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:38:52.019571Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:39:52.080953Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:40:52.142420Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:41:52.203734Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:42:52.264937Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:43:52.326508Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:44:52.387995Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:45:52.449439Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T15:46:52.467493Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:09:03.913088Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:10:03.970729Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:11:04.030479Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:12:04.090546Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:13:04.140566Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:14:04.157922Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:15:04.219174Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:16:04.280334Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:17:04.295600Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:18:04.356366Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:19:04.360655Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:20:04.369292Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:21:04.371555Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:22:04.396784Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:23:04.457530Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:24:04.518574Z | Info | Live bytes: 782.24MB Heap size: 2669.67MB +2024-07-03T16:24:26.799240Z | Info | LSP: received shutdown +2024-07-03T16:24:26.802265Z | Error | Got EOF +2024-07-03 20:11:45.9890000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-03 20:11:45.9910000 [client] INFO Finding haskell-language-server +2024-07-03 20:11:45.9930000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:45.9930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.0000000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-03 20:11:46.2900000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:46.2900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.2950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 20:11:46.4350000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:46.4350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.4400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-03 20:11:46.5600000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:46.5600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.5640000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-03 20:11:46.6840000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:46.6840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.6900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 20:11:46.7040000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:46.7050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.7130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-03 20:11:46.7270000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:46.7270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.7310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-03 20:11:46.7510000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-03 20:11:46.7880000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:46.7890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:46.7920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-03 20:11:46.9060000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-03 20:11:46.9070000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-03 20:11:53.1770000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-03 20:11:53.2340000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-03 20:11:53.2340000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:53.2340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:53.2420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-03 20:11:53.3270000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:53.3270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:53.3320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-03 20:11:53.3480000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:53.3480000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:53.3550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-03 20:11:53.3680000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:53.3690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:53.3740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-03 20:11:53.3880000 [client] INFO Checking for ghcup installation +2024-07-03 20:11:53.3880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-03 20:11:53.3920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-03 20:11:53.4770000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-03 20:11:53.4770000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 20:11:53.4770000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-03 20:11:53.4770000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03 20:11:53.4770000 [client] INFO server environment variables: +2024-07-03 20:11:53.4770000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-03 20:11:53.4770000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-03 20:11:53.4770000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-03 20:11:53.4780000 [client] INFO Starting language server +2024-07-03T20:12:02.812818Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-03T20:12:02.813836Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-03T20:12:02.814215Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T20:12:02.817911Z | Info | Logging heap statistics every 60.00s +2024-07-03T20:12:02.825891Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-03T20:12:02.826666Z | Info | Starting server +2024-07-03T20:12:02.828188Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-03T20:12:02.893936Z | Info | Started LSP server in 0.07s +2024-07-03T20:12:04.173866Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Value.hs +2024-07-03T20:12:04.174879Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-03T20:12:04.733585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T20:12:05.720869Z | Info | Load cabal cradle using single file +2024-07-03T20:12:06.574440Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT833163-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-03T20:12:09.626194Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-914364913aa32f3c16b7cecf47a795d21f367459 +2024-07-03T20:12:09.630975Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-03T20:13:02.870673Z | Info | Live bytes: 316.21MB Heap size: 1527.78MB +2024-07-03T20:14:02.931628Z | Info | Live bytes: 316.21MB Heap size: 1527.78MB +2024-07-03T20:15:02.940445Z | Info | Live bytes: 316.21MB Heap size: 1527.78MB +2024-07-03T20:16:02.994628Z | Info | Live bytes: 316.21MB Heap size: 1527.78MB +2024-07-03T20:17:03.055838Z | Info | Live bytes: 316.21MB Heap size: 1527.78MB +2024-07-03T20:18:03.116465Z | Info | Live bytes: 316.21MB Heap size: 1527.78MB +2024-07-03T20:19:03.177526Z | Info | Live bytes: 316.21MB Heap size: 1527.78MB +2024-07-03T20:19:49.276322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T20:19:52.411583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-03T20:20:03.187928Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:21:03.249748Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:22:03.310373Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:23:03.364404Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:24:03.380882Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:25:03.404407Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:26:03.465176Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:27:03.510008Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:28:03.568316Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:29:03.628446Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:30:03.685428Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:31:03.746130Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:32:03.776776Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:33:03.782080Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:34:03.843409Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:35:03.844643Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:36:03.904450Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:37:03.908649Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:38:03.937990Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:39:03.998787Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:40:04.005981Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:41:04.067154Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:42:04.115562Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:43:04.176044Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:44:04.177163Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:45:04.237585Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:46:04.298434Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:47:04.336615Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:48:04.381110Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:49:04.390547Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:50:04.452033Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:51:04.490835Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:52:04.521309Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:53:04.582784Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:54:04.644436Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:55:04.676753Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:56:04.738137Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:57:04.799692Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:58:04.860604Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T20:59:04.895175Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:00:04.955988Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:01:05.016658Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:02:05.078187Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:03:05.108809Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:04:05.170214Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:05:05.204837Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:06:05.207411Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:07:05.229455Z | Info | Live bytes: 381.66MB Heap size: 1752.17MB +2024-07-03T21:07:12.090797Z | Error | Got EOF +2024-07-04 06:05:29.7790000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-04 06:05:29.7810000 [client] INFO Finding haskell-language-server +2024-07-04 06:05:29.7830000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:29.7830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:29.7910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-04 06:05:30.1440000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:30.1450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:30.1500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-04 06:05:30.3380000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:30.3380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:30.3450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-04 06:05:30.4910000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:30.4910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:30.4970000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-04 06:05:30.7100000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:30.7100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:30.7150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-04 06:05:30.7290000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:30.7290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:30.7350000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-04 06:05:30.7540000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:30.7540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:30.7600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-04 06:05:30.7790000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-04 06:05:30.8290000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:30.8290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:30.8350000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-04 06:05:31.0210000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-04 06:05:31.0220000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-04 06:05:39.5900000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-04 06:05:39.8620000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-04 06:05:39.8620000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:39.8620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:39.8660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-04 06:05:39.9510000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:39.9510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:39.9560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-04 06:05:39.9740000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:39.9740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:39.9780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-04 06:05:39.9920000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:39.9920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:39.9960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-04 06:05:40.0090000 [client] INFO Checking for ghcup installation +2024-07-04 06:05:40.0090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-04 06:05:40.0130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-04 06:05:40.1280000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-04 06:05:40.1280000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-04 06:05:40.1280000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-04 06:05:40.1280000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-04 06:05:40.1280000 [client] INFO server environment variables: +2024-07-04 06:05:40.1280000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-04 06:05:40.1280000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-04 06:05:40.1280000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-04 06:05:40.1300000 [client] INFO Starting language server +2024-07-04T06:05:49.792903Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-04T06:05:49.794433Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-04T06:05:49.794647Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-04T06:05:49.797775Z | Info | Logging heap statistics every 60.00s +2024-07-04T06:05:49.804880Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-04T06:05:49.805358Z | Info | Starting server +2024-07-04T06:05:49.818525Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-04T06:05:49.910698Z | Info | Started LSP server in 0.11s +2024-07-04T06:05:51.134134Z | Info | Cradle path: cardano-api/internal/Cardano/Api/SerialiseRaw.hs +2024-07-04T06:05:51.135197Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-04T06:05:51.698846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T06:05:52.539441Z | Info | Load cabal cradle using single file +2024-07-04T06:05:53.375266Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT7966-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-04T06:05:56.599704Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-914364913aa32f3c16b7cecf47a795d21f367459 +2024-07-04T06:05:56.607731Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-04T06:06:49.851556Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:07:49.912808Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:08:49.973936Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:09:50.034935Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:10:50.096157Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:11:50.157416Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:12:50.218393Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:13:50.265861Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:14:50.270969Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:15:50.278943Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:16:50.293967Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:17:50.327087Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:18:50.367013Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:19:50.427938Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:20:50.443215Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:21:50.463034Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:22:50.524131Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:23:50.585214Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:24:50.646321Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:25:50.707174Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:26:50.768065Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:27:50.829021Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:28:50.890063Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:29:50.951052Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:30:50.981113Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:31:50.991888Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:32:51.052995Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:33:51.114065Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:34:51.175144Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:35:51.236308Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:36:51.262989Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:37:51.324111Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:38:51.366754Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:39:51.427842Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:40:51.488770Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:41:51.549920Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:42:51.611039Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:43:51.671990Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:44:51.712085Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:45:51.752999Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:46:51.800344Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:47:51.861466Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:48:51.922379Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:49:51.983265Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:50:52.044304Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:51:52.105331Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:52:52.128901Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:53:52.189949Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:54:52.223011Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:55:52.283988Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:56:52.329494Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:57:52.390589Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:58:52.451699Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T06:59:52.512657Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:00:52.573727Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:01:52.574948Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:02:52.635751Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:03:52.696915Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:04:52.757926Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:05:52.818984Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:06:52.880064Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:07:52.941056Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:08:53.001865Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:09:53.062586Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:10:53.119047Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:11:53.180290Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:12:53.240856Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:13:53.260446Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:14:53.321491Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:15:53.382416Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:16:53.443423Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:17:53.504088Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:18:53.565173Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:19:53.582456Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:20:53.603146Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:21:53.662901Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:22:53.719001Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:23:53.727066Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:24:53.759041Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:25:53.820201Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:26:53.847802Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:27:53.855088Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:28:53.909975Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:29:53.929944Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:30:53.981930Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:31:54.008033Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:32:54.069392Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:33:54.130537Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:34:54.192124Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:35:54.253274Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:36:54.314528Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:37:54.333045Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:38:54.352951Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:39:54.360502Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:40:54.421687Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:41:54.431030Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:42:54.463076Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:43:54.524271Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:44:54.557220Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:45:54.618283Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:46:54.679256Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:47:54.719081Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:48:54.744122Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:49:54.760037Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:50:54.821052Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:51:54.873179Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:52:54.934048Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:53:54.991113Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:54:55.032866Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:55:55.093956Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:56:55.154895Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:57:55.215808Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:58:55.225842Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T07:59:55.262964Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:00:55.323916Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:01:55.385082Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:02:55.446110Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:03:55.507358Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:04:55.551064Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:05:55.611792Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:06:55.672555Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:07:55.733760Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:08:55.746804Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:09:55.752190Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:10:55.813377Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:11:55.874683Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:12:55.935831Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:13:55.997020Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:14:56.058184Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:15:56.118800Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:16:56.179022Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:17:56.213680Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:18:56.274796Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:19:56.315944Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:20:56.350991Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:21:56.371001Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:22:56.432049Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:23:56.478906Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:24:56.539916Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:25:56.600899Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:26:56.604318Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:27:56.665432Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:28:56.726404Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:29:56.752072Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:30:56.770585Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:31:56.831578Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:32:56.891984Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:33:56.952863Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:34:57.013795Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:35:57.055065Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:36:57.116210Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:37:57.177389Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:38:57.238664Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:39:57.299870Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:40:57.360998Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:41:57.421996Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:42:57.430991Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:43:57.438354Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:44:57.499268Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:45:57.542281Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:46:57.582465Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:47:57.643899Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:48:57.705158Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:49:57.766306Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:50:57.827510Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:51:57.887047Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:52:57.948235Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:53:57.951059Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:54:58.012227Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:55:58.015109Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:56:58.076303Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:57:58.137144Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:58:58.198479Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T08:59:58.254999Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:00:58.316332Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:01:58.377730Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:02:58.421174Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:03:58.439031Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:04:58.500027Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:05:58.527023Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:06:58.588049Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:07:58.649059Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:08:58.687057Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:09:58.703078Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:10:58.764230Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:11:58.825176Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:12:58.886141Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:13:58.947224Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:14:59.008395Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:15:59.039026Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:16:59.100052Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:17:59.111089Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:18:59.145506Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:19:59.205816Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:20:59.265925Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:21:59.325925Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:22:59.385880Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:23:59.445817Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:24:59.506593Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:25:59.538944Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:26:59.599847Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:27:59.660578Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:28:59.711030Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:29:59.771910Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:30:59.804551Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:31:59.864781Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:32:59.924840Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:33:59.928808Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:34:59.955299Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:36:00.015933Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:37:00.031982Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:38:00.092968Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:39:00.150949Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:40:00.210956Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:41:00.223113Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:42:00.283972Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:43:00.286992Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:44:00.319062Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:45:00.325751Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:46:00.386428Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:47:00.436349Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:48:00.485375Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:49:00.546388Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T09:50:00.607690Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:10:53.324862Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:11:53.365454Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:12:53.369073Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:13:53.377280Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:14:53.413623Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:15:53.415382Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:16:53.436262Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:17:53.484751Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:18:53.545173Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:19:53.575144Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:20:53.598424Z | Info | Live bytes: 82.71MB Heap size: 1241.51MB +2024-07-04T10:21:33.207988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:21:53.616482Z | Info | Live bytes: 368.67MB Heap size: 1752.17MB +2024-07-04T10:22:53.670057Z | Info | Live bytes: 368.67MB Heap size: 1752.17MB +2024-07-04T10:23:53.680551Z | Info | Live bytes: 368.67MB Heap size: 1752.17MB +2024-07-04T10:24:15.287828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:24:53.717864Z | Info | Live bytes: 388.42MB Heap size: 1752.17MB +2024-07-04T10:25:53.778237Z | Info | Live bytes: 388.42MB Heap size: 1752.17MB +2024-07-04T10:26:53.838283Z | Info | Live bytes: 388.42MB Heap size: 1752.17MB +2024-07-04T10:27:22.713603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:27:53.868898Z | Info | Live bytes: 427.49MB Heap size: 1752.17MB +2024-07-04T10:28:53.883019Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:29:53.908581Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:30:53.969385Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:31:53.975272Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:32:54.036319Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:33:54.097291Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:34:54.157502Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:35:54.218274Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:36:54.263791Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:37:54.324814Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:38:54.346856Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:39:54.407294Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:40:54.468061Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:41:54.528369Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:42:54.589662Z | Info | Live bytes: 437.04MB Heap size: 1752.17MB +2024-07-04T10:43:11.876168Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Scripts/New.hs +2024-07-04T10:43:11.876716Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-04T10:43:11.904791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:13.399209Z | Info | Load cabal cradle using single file +2024-07-04T10:43:13.973421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:14.374978Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT7966-5 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-04T10:43:14.646056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:15.416523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:16.009352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:16.597600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:17.462920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:17.674828Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-914364913aa32f3c16b7cecf47a795d21f367459 +2024-07-04T10:43:17.675401Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-914364913aa32f3c16b7cecf47a795d21f367459 +2024-07-04T10:43:17.681210Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-04T10:43:18.255353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:18.968984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:19.568032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:19.927102Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:43:19.983011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:43:20.099565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:43:20.151234Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:43:20.334426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:20.352062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:43:21.130063Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:43:21.211801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:21.779103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:22.458529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:23.700869Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:24.492539Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:24.720398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:25.441312Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:25.675310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:25.941977Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:26.297870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:26.318122Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:27.429630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:27.488809Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:27.884183Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:28.242006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:29.871854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:30.450928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:30.673919Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:31.032840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:31.401973Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:31.644727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:31.969400Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:32.271863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:33.405680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:47.032224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:47.775931Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:48.134064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:49.831691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:49.965168Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:51.111965Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:51.163654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:52.359985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:52.938013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:52.953395Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:53.617268Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:53.975056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:54.563329Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:54.590894Z | Info | Live bytes: 806.27MB Heap size: 2533.36MB +2024-07-04T10:43:54.844685Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:55.145945Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:55.207830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:55.463906Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:55.822891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:56.436804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:56.448422Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:57.266790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:57.881301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:58.110479Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:58.468465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:59.122355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:43:59.553409Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:43:59.778045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:00.261659Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:00.452387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:00.534538Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:02.872770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:03.039410Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:03.882470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:03.960432Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:05.290212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:05.800124Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:05.912556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:11.859882Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:12.218751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:12.880394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:13.157851Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:13.516978Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:13.596441Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:14.169116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:14.320689Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:14.903737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:14.961665Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:16.084480Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:16.105037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:16.698865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:17.322937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:17.930056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:18.132714Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:18.491258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:19.150494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:19.569270Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:19.802730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:26.359257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:26.424759Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:26.932073Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:27.033551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:27.642377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:27.940035Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:28.204831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:28.851034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:29.040909Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:29.302463Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:29.649819Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:29.659954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:30.069617Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:30.301149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:30.871114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:30.950710Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:34.559606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:34.996073Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:35.188213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:35.547640Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:35.905685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:36.528006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:37.159429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:37.611839Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:44:37.781101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:44:54.596819Z | Info | Live bytes: 824.76MB Heap size: 2533.36MB +2024-07-04T10:45:54.657367Z | Info | Live bytes: 824.76MB Heap size: 2533.36MB +2024-07-04T10:46:29.047629Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:46:29.220591Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:29.447673Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:29.578602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:30.333275Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:30.689324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:31.274184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:31.275926Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:31.642243Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:31.999730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:32.308190Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:32.668351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:33.173817Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:33.530869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:34.098565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:34.684447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:34.693789Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:35.607848Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:35.627669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:36.370039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:36.845208Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:37.011340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:37.444524Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:37.684338Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:38.026880Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:38.311926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:38.864369Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:38.881452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:39.540274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:39.904868Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:40.161423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:40.471621Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:40.831319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:41.059782Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:41.418799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:41.722797Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:42.079855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:42.851700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:43.491438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:44.183323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:44.193940Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:44.924079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:45.560662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:46.229609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:46.845591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:46:46.874389Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:46:54.665964Z | Info | Live bytes: 841.94MB Heap size: 2533.36MB +2024-07-04T10:47:54.677562Z | Info | Live bytes: 841.94MB Heap size: 2533.36MB +2024-07-04T10:48:54.738527Z | Info | Live bytes: 841.94MB Heap size: 2533.36MB +2024-07-04T10:49:54.799323Z | Info | Live bytes: 841.94MB Heap size: 2533.36MB +2024-07-04T10:50:38.908801Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:39.266748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:40.940429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:41.543163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:42.109306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:42.694264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:43.130618Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:43.288363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:43.460860Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:44.077540Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:44.644120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:45.292698Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:45.308370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:45.991651Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:46.006186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:46.254724Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:46.614208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:48.777246Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:49.134786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:49.930532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:50.507890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:51.021201Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:51.132400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:51.314506Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:52.479269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:53.050504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:53.108971Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:53.425811Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:53.782275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:54.106174Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:54.372965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:54.566053Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:54.800052Z | Info | Live bytes: 853.97MB Heap size: 2533.36MB +2024-07-04T10:50:55.738563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:55.831943Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:56.586145Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:56.944452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:57.528951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:58.110044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:58.585694Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:50:58.675673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:59.471935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:50:59.686997Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:00.045155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:00.746375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:01.410226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:01.577492Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:02.326327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:02.660161Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:02.957580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:04.819796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:51:04.982907Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:05.341137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:05.655711Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:06.010389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:06.104447Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:06.330910Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:06.689822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:13.434518Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:13.794574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:14.128733Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:14.475457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:51:14.491982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:14.649803Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:15.362394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:51:15.895101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:16.600886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:17.210534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:17.457130Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:17.809950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:19.467271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:19.615973Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:20.027815Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:20.205762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:20.543444Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:20.900771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:21.503579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:22.089686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:22.300912Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:22.666173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:23.305610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:23.804108Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:23.886185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:24.143531Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:24.504372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:24.964570Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:25.116573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:25.578788Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:25.720061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:26.356560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:27.017567Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:27.045367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:27.394331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:51:27.562508Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:27.698888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:28.298462Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:51:28.471301Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:28.829075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:29.109370Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:29.466476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:31.266485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:32.024995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:32.063887Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:32.672355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:32.967349Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:33.325051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:33.360226Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:33.623462Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:33.979700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:34.674486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:35.071666Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:35.284413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:35.785277Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:35.988859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:36.512740Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:36.872601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:37.306621Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:37.462681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:38.044240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:38.712467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:38.754285Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:39.308060Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:39.665593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:39.978227Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:40.337141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:40.500812Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:41.063069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:41.301055Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:41.658332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:41.929414Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:42.081869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T10:51:42.255830Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:42.287595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:42.357950Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T10:51:42.644674Z | Warning | codeRange: no HieAst exist for file +2024-07-04T10:51:43.005256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T10:51:54.811391Z | Info | Live bytes: 882.26MB Heap size: 2533.36MB +2024-07-04T10:52:54.856878Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T10:53:54.887552Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T10:54:54.948211Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T10:55:54.992285Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T10:56:55.033499Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T10:57:55.094201Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T10:58:55.119159Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T10:59:55.180270Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:00:55.237357Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:01:55.298218Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:02:55.358355Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:03:55.364020Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:04:55.376704Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:05:55.403460Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:06:55.435050Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:07:55.495347Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:08:55.555169Z | Info | Live bytes: 887.67MB Heap size: 2533.36MB +2024-07-04T11:09:47.546192Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:47.683870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:49.012609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:49.566669Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:49.656564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:50.332220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:50.865200Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:50.938361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:51.498570Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:51.528617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:52.087165Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:52.369001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:52.462505Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:53.059820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:53.680172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:54.321130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:54.750507Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:54.992394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:55.556080Z | Info | Live bytes: 887.12MB Heap size: 2533.36MB +2024-07-04T11:09:55.570525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:56.290473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:56.907929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:57.457111Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:57.503705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:57.851216Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:58.100175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:58.491178Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:58.742420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:09:59.493588Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:09:59.677568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:00.046343Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:00.405665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:01.370709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:01.640313Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:01.999984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:02.469022Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:02.678879Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:02.697721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:03.287829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:03.906212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:04.509463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:04.638429Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:07.342640Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:07.382871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:08.282940Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:08.505702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:08.670120Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:08.885366Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:10:09.242426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:10:55.603674Z | Info | Live bytes: 896.90MB Heap size: 2533.36MB +2024-07-04T11:11:40.631802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:11:55.617638Z | Info | Live bytes: 896.90MB Heap size: 2533.36MB +2024-07-04T11:12:55.678731Z | Info | Live bytes: 896.90MB Heap size: 2533.36MB +2024-07-04T11:13:20.437578Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:20.793622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:25.003149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:25.356307Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:25.639761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:25.764539Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:26.623061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:27.193975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:27.362910Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:28.137156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:28.748902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:29.336864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:30.016315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:30.615252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:30.859417Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:31.218687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:31.312361Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:31.762193Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:31.928197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:32.569665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:32.740632Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:33.355986Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:33.599783Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:33.713875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:34.542791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:34.805939Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:35.163294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:35.368321Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:13:35.727450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:13:55.699296Z | Info | Live bytes: 915.24MB Heap size: 2533.36MB +2024-07-04T11:14:39.028211Z | Warning | codeRange: no HieAst exist for file +2024-07-04T11:14:39.201715Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:40.159776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:40.344441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:40.418804Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:40.519986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:40.687199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:41.050414Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:41.276732Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:41.462115Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:41.553160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:41.577793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:41.622125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:41.737022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:42.160442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:42.516567Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:42.659511Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:42.963860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:48.330067Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:14:48.864708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:49.742020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:50.494833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:51.160637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:51.774138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:52.344906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:52.965115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:53.572169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:54.140360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:54.754647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:55.700533Z | Info | Live bytes: 925.11MB Heap size: 2533.36MB +2024-07-04T11:14:55.736855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:56.350107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:56.961657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:57.533974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:58.119877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:58.745665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:14:59.373861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:01.267874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:02.122115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:02.758134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:03.861447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:04.432761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:05.121327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:06.842367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:07.557958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:08.135394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:09.552309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:10.208303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:10.344255Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:15:10.882214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:10.904939Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:15:11.558008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:15:55.733059Z | Info | Live bytes: 936.13MB Heap size: 2533.36MB +2024-07-04T11:16:55.794029Z | Info | Live bytes: 936.13MB Heap size: 2533.36MB +2024-07-04T11:17:08.950853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:10.275721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:11.043700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:12.062704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:12.246103Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:12.313501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:12.778554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:13.914552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:14.119694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:14.241256Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:14.350897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:14.427340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:14.541709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:14.647237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:14.678824Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:14.963578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:15.191318Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:15.213382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:15.345599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:15.527259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:15.881939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:16.463254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:17.227682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:17.586133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:17.665097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:18.116729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:18.891809Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:19.426190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:24.792833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:26.721853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:27.910606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:28.471849Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:28.565697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:28.654279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:28.904788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:29.052042Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:29.146532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:29.180215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:29.236817Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:29.549796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:29.721444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:29.768962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:29.891196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:29.962956Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:30.041778Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:30.091073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:17:30.429903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:17:55.820218Z | Info | Live bytes: 948.24MB Heap size: 2533.36MB +2024-07-04T11:18:12.680169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:32.353004Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:32.418169Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:32.571991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:33.192124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:33.718516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:44.660554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:44.778112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:44.943802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:45.086566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:45.162961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:45.299358Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:45.358418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:45.726745Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:45.887626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:46.103261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:46.271531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:46.451749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:46.629574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:46.909801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:46.980472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:47.339514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:47.442084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:48.247470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:48.603924Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:48.662960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:48.790097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:49.135556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:49.135639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:49.198024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:49.296671Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:18:49.721656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:18:55.827520Z | Info | Live bytes: 957.69MB Heap size: 2533.36MB +2024-07-04T11:19:02.628887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:19:04.115424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:19:04.138367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:19:55.879430Z | Info | Live bytes: 957.69MB Heap size: 2533.36MB +2024-07-04T11:20:03.375617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:22.669339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:23.660662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:24.503312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:25.118246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:25.773695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:26.360343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:27.072451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:27.838020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:28.484830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:29.396779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:30.286968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:30.975545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:31.788531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:32.565665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:33.183006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:33.768403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:34.406985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:34.976007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:35.672674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:36.863528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:37.474942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:38.097741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:39.173945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:39.758250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:40.633898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:41.233866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:41.994564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:42.673316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:43.248709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:46.473521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:47.254445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:50.687690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:51.361793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:51.997790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:52.865049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:53.817243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:54.480068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:55.882556Z | Info | Live bytes: 982.29MB Heap size: 2533.36MB +2024-07-04T11:20:57.600003Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:20:58.108379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:59.035747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:20:59.729008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:00.335495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:01.057917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:01.680619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:02.339842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:03.044544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:03.711272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:04.330988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:04.966078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:05.655565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:06.226384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:06.804632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:07.502110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:08.183257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:08.807300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:09.433008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:10.044443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:10.641605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:11.273291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:12.192474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:12.956797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:14.574542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:15.274575Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:15.984068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:17.762326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:18.342897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:18.963249Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:19.499543Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:20.085762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:20.674794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:21.362714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:21.962897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:22.656000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:23.232830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:23.876641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:24.606573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:25.187772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:25.771476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:26.422784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:27.045194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:27.703920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:28.391764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:28.958397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:29.581722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:29.642537Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:30.177108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:30.318181Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:30.482837Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:30.852663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:31.571823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:32.662579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:33.464852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:51.433798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:51.582069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:51.692101Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:51.759358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:21:51.962908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:54.531299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:55.695592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:55.883926Z | Info | Live bytes: 1039.43MB Heap size: 2533.36MB +2024-07-04T11:21:56.967763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:58.091480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:21:59.397450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:00.018643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:00.996495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:01.636634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:02.257116Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:22:02.297419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:22:02.394533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:22:02.656420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:05.054370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:06.538676Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:22:07.057640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:07.847588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:08.513383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:09.082038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:10.071539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:10.742179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:11.451879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:11.867460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:22:11.959554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:22:12.298335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:22:12.320801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:22:55.928604Z | Info | Live bytes: 1038.73MB Heap size: 2533.36MB +2024-07-04T11:23:55.989406Z | Info | Live bytes: 1038.73MB Heap size: 2533.36MB +2024-07-04T11:24:16.235465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:24:16.281806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:24:16.758484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:24:16.954749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:24:17.006060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:24:17.132501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:24:17.189127Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:24:17.489974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:24:17.744425Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:24:18.454967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:24:56.019377Z | Info | Live bytes: 1068.17MB Heap size: 2533.36MB +2024-07-04T11:25:23.177742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:27.342284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:30.282790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:31.264708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:32.392217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:34.580334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:35.180714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:36.457391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:37.499872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:39.713442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:40.732960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:41.652605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:25:56.034317Z | Info | Live bytes: 1060.86MB Heap size: 2533.36MB +2024-07-04T11:26:37.960846Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:26:38.004378Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:26:38.173976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:26:38.215724Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:26:38.275668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:26:38.337154Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:26:38.464563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:26:38.930772Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:26:39.205240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:26:46.942693Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-04T11:26:47.549563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:26:48.638785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:26:49.806351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:26:56.040779Z | Info | Live bytes: 1094.04MB Heap size: 2533.36MB +2024-07-04T11:27:54.365331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:27:54.557005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:27:54.604980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:27:54.678011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:27:54.731279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:27:54.813002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:27:55.320887Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:27:55.384489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:27:56.027845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:27:56.042668Z | Info | Live bytes: 1111.39MB Heap size: 2533.36MB +2024-07-04T11:28:56.044305Z | Info | Live bytes: 1111.39MB Heap size: 2533.36MB +2024-07-04T11:28:57.761874Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:57.831677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:57.999997Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:58.142076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:28:58.986003Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:58.986400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:28:59.066966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:59.170011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:59.302811Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:59.409224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:28:59.598624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:02.479681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:03.085837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:03.746616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:04.355888Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:04.526206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:06.762718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:07.383071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:07.646771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:08.014208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:08.172970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:08.409914Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:08.604684Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:08.702170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:08.711993Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:08.845540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:08.902493Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:09.185609Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:09.368682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:09.434218Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:09.547234Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:09.966395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:10.637335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:10.639853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:10.776958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:10.843785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:10.914604Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:11.311566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:12.010039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:12.620508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:12.863857Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:12.970579Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:13.077991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:13.141538Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:13.213374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:13.786989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:14.496040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:18.796841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:19.867644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:27.729670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:28.340968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:28.720164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:28.915180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:29.673292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:30.472335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:31.222914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:32.053801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:32.630200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:33.545709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:33.564000Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:29:34.461996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:37.283764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:38.505292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:29:56.058724Z | Info | Live bytes: 1141.26MB Heap size: 2533.36MB +2024-07-04T11:30:11.864460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:11.907335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:12.089298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:12.151884Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:12.178724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:12.189728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:12.743599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:13.331425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:13.928059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:14.258696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:14.527823Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:14.638025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:14.666519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:14.783428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:14.857060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:14.950789Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:15.033047Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:15.291615Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-04T11:30:15.333878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:18.716916Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:18.846384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.022842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.128721Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.226358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.238708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:19.271932Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.355620Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.631425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.809962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:19.815149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:19.931149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:20.050615Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:20.143328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:20.245809Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:20.296532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:20.468325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:33.860606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:34.147722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:34.334988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:34.519243Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:34.597336Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:34.635821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:34.693791Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:34.870948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:34.933613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:35.039361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:35.131393Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:35.232107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:35.394844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:35.458809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:36.037610Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:36.146231Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:36.210063Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:36.349362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:36.574807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:37.157731Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:37.251755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:37.470179Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:37.644095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:37.707850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:37.890685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:37.907509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:37.973520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:38.510927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:38.538246Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-04T11:30:41.272662Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:41.496628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:41.740714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:42.027696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:42.115380Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:42.120927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:42.298621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:42.379779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:42.447008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:42.531365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:30:42.824924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:42.940578Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-04T11:30:43.679126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:48.469642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:49.062266Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-04T11:30:52.961909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:54.383160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:55.359364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:56.060794Z | Info | Live bytes: 1269.57MB Heap size: 2533.36MB +2024-07-04T11:30:59.062772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:30:59.717700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:01.184059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:02.529868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:03.529427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:04.411803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:05.325908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:06.494202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:07.823782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:08.604199Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:31:41.748636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:31:56.076800Z | Info | Live bytes: 1272.73MB Heap size: 2581.59MB +2024-07-04T11:32:56.129372Z | Info | Live bytes: 1272.73MB Heap size: 2581.59MB +2024-07-04T11:32:57.491694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:33:56.184395Z | Info | Live bytes: 1272.73MB Heap size: 2581.59MB +2024-07-04T11:34:16.292131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:17.261496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:17.343948Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:17.447581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:17.507742Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:17.571791Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:17.692261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:17.706684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:17.769613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:18.304716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:18.555974Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:18.730711Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:18.811539Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:18.896827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:19.297365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:19.422469Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:19.827602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:21.039353Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:21.178203Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:21.329663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:21.525718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:22.418343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:23.081957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:23.807632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:24.375067Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:24.399621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:25.042583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:26.244972Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:26.300327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:26.327595Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:26.572572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:26.881724Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:27.103156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:27.180703Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:27.225616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:27.334302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:27.709816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:29.677305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:30.351531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:30.416639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:30.529036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:30.652791Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:30.759304Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:30.887132Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:30.954557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:31.065836Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:31.603891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:32.749768Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:32.759574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:32.993443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:33.529607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:34.397045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:35.111836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:36.211296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:37.115780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:37.484886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:37.770419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:38.647739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:38.768992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:39.823676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:39.831676Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:39.881693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:40.124995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:40.282130Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:40.384895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:40.416865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:40.443375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:40.859375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:40.986103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:41.000988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:41.153659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:34:41.687365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:42.500122Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:52.893769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:53.387524Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:34:53.586124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:34:56.187325Z | Info | Live bytes: 1336.97MB Heap size: 2617.25MB +2024-07-04T11:35:03.121557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:03.760980Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:35:03.847854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:20.145144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:21.558526Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:21.743012Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:21.788666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:21.885375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:21.954928Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:22.005048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:22.616669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:23.447079Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:35:23.741141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:27.729837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:31.302267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:31.919355Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:35:32.538940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:39.137234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:42.908359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:50.501827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:50.661856Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:50.725310Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:50.824031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:50.857108Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:50.953044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:51.504811Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:35:51.748598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:53.546723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:35:53.668955Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:35:56.190522Z | Info | Live bytes: 1423.43MB Heap size: 2671.77MB +2024-07-04T11:35:59.207370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:35:59.726160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:00.988603Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:36:01.509180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:02.471950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:36:02.981124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:03.481573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:36:04.003692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:05.359945Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T11:36:05.876749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:16.530491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:17.719843Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T11:36:17.934278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:28.210588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T11:36:56.219394Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T11:37:56.279311Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:14:32.132386Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:15:32.193404Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:16:32.255087Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:17:32.316827Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:18:32.378188Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:19:32.432712Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:20:32.438043Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:21:32.440713Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:22:32.472661Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:23:32.533568Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:24:32.588295Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:25:32.649535Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:26:32.710828Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:27:32.772107Z | Info | Live bytes: 773.01MB Heap size: 3143.63MB +2024-07-04T12:28:32.832958Z | Info | Live bytes: 779.78MB Heap size: 3143.63MB +2024-07-04T12:28:41.553410Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T12:29:32.882537Z | Info | Live bytes: 792.94MB Heap size: 3143.63MB +2024-07-04T12:29:33.047776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T12:29:33.164799Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T12:29:33.231904Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T12:29:33.556307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T12:29:33.798395Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T12:29:34.311711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T12:29:34.986987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T12:29:35.673209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T12:29:35.693897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T12:29:35.783876Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T12:29:35.878496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T12:29:36.302253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T12:29:36.947602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T12:29:49.775377Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T12:30:32.897822Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:31:32.917505Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:32:32.978852Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:33:33.040155Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:34:33.101420Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:35:33.136863Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:36:33.197376Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:37:33.257557Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:38:33.288792Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:39:33.350506Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:40:33.411643Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:41:33.461376Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:42:33.522372Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:43:33.528816Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:44:33.540733Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:45:33.602149Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:46:33.624723Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:47:33.655862Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:48:33.690323Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:49:33.751554Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:50:33.784720Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:51:33.845976Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:52:33.906401Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:53:33.961324Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:54:34.022213Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:55:34.063573Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:56:34.098062Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:57:34.158974Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:58:34.216810Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T12:59:34.278064Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:00:34.334664Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:01:34.377124Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:02:34.398826Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:03:34.457277Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:04:34.517409Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:05:34.578301Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:06:34.638412Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:07:34.698439Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:08:34.758342Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:09:34.818523Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:10:34.878286Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:11:34.938317Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:12:34.998454Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:13:35.058340Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:14:35.118321Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:15:35.178288Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:16:35.238420Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:17:35.298419Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:18:35.358426Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:19:35.418292Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:20:35.478364Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:21:35.538385Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:22:35.598388Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:23:35.658316Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:24:35.718395Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:25:35.778428Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:26:35.838339Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:27:35.898335Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:28:35.958432Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:29:35.960681Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:30:36.022147Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:31:36.082420Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:32:36.124142Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:33:36.184451Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:34:36.245114Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:35:36.305355Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:36:36.328336Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:37:36.388361Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:38:36.448472Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:39:36.508410Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:40:36.568300Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:41:36.628400Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:42:36.688466Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:43:36.748465Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:44:36.808298Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:45:36.868943Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:46:36.900439Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:47:36.960408Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:48:37.020302Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:49:37.080341Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:50:37.140587Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:51:37.200549Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:52:37.261477Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:53:37.321312Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:54:37.381526Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:55:37.442243Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:56:37.463421Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:57:37.524199Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:58:37.584762Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T13:59:37.589403Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:00:37.649515Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:01:37.709348Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:02:37.762731Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:03:37.822377Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:04:37.883126Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:05:37.943379Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:06:38.003402Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:07:38.063414Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:08:38.123460Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:09:38.183326Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:10:38.243303Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:11:38.303431Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:12:38.363365Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:13:38.423424Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:14:38.439016Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:15:38.499364Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:16:38.560853Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:17:38.622401Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:18:38.683904Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:19:38.745647Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:20:38.750534Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:21:38.785078Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:22:38.826611Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:23:38.887781Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:24:38.896857Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:25:38.958446Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:26:39.019721Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:27:39.080629Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:28:39.141725Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:29:39.202391Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:30:39.239699Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:31:39.300518Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:32:39.360578Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:33:39.420421Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:34:39.481097Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:35:39.498148Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:36:39.532428Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:37:39.556203Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:38:39.616432Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:39:39.677458Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:40:39.738540Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:41:39.757386Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:42:39.818204Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:43:39.865588Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:44:39.927014Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:45:39.938154Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:46:39.999014Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:47:40.059410Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:48:40.120240Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:49:40.161360Z | Info | Live bytes: 795.79MB Heap size: 3143.63MB +2024-07-04T14:49:55.690057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:04.773183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:04.941992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:04.978881Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:05.003003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:05.072341Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:05.104773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:05.595013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:05.780809Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T14:50:06.486218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:13.218008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:13.716728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:13.834460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:13.877703Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:13.947383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:13.997583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:14.112325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:14.156182Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:14.178616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:14.731384Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:50:14.744596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:14.952730Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:15.129801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:15.179416Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:15.294483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:15.393077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:16.660159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:16.746968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:16.840243Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:16.894534Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:50:17.263127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:18.905537Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:50:24.906041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:50:40.178636Z | Info | Live bytes: 840.28MB Heap size: 3143.63MB +2024-07-04T14:51:04.890348Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:51:09.025762Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:51:09.957266Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:51:10.332632Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:51:10.686991Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:51:11.493929Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T14:51:16.457160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:51:16.643864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:51:16.669486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:51:16.745223Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:51:16.901206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T14:51:17.274661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:51:17.893728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T14:51:40.203322Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:52:40.264597Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:53:40.325700Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:54:40.386450Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:55:40.446478Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:56:40.506560Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:57:40.566450Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:58:40.626577Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T14:59:40.687373Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:00:40.748487Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:01:40.788574Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:02:40.806385Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:03:40.824664Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:04:40.885965Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:05:40.947324Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:06:41.008570Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:07:41.069810Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:08:41.131152Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:09:41.192384Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:10:41.253517Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:11:41.314763Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:12:41.376060Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:13:41.437413Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:14:41.498731Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:15:41.560071Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:16:41.621403Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:17:41.682712Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:18:41.734968Z | Info | Live bytes: 853.59MB Heap size: 3143.63MB +2024-07-04T15:18:52.733806Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T15:18:53.696604Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:18:53.899200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:18:54.436128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:18:54.960032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:18:55.733322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:18:55.946541Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:18:56.070004Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:18:56.418733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:18:57.294516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:18:57.466588Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-04T15:19:02.289459Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T15:19:02.897475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:19:41.737096Z | Info | Live bytes: 857.96MB Heap size: 3143.63MB +2024-07-04T15:20:03.658042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:04.237800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:05.043562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:05.684376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:06.307986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:06.349158Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:20:06.876195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:07.697550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:08.457917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:09.099673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:09.974899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:20:41.764946Z | Info | Live bytes: 870.18MB Heap size: 3143.63MB +2024-07-04T15:21:18.052812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:24.571308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:28.648696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:32.268160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:34.674795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:35.110182Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:35.324352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:35.906687Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T15:21:41.767061Z | Info | Live bytes: 1017.84MB Heap size: 3143.63MB +2024-07-04T15:21:47.300486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:47.499665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:47.586062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:47.683831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:47.768345Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:47.815444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:47.888290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:48.047465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:48.410621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:49.043412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:49.280284Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:49.570627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:21:49.747239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:49.891212Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:50.006957Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:50.151158Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:21:50.273953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:03.105721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:11.666272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:12.463429Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T15:22:12.697555Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:15.665548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:22:15.737237Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:22:15.853120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:22:15.962715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:22:16.180636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:18.290612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:19.395778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:33.249213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:34.984606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:37.379530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:41.773589Z | Info | Live bytes: 1075.03MB Heap size: 3143.63MB +2024-07-04T15:22:44.963945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:46.894344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:48.304914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:49.218251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:49.844335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:50.517344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:22:50.547729Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T15:22:51.271004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:14.447459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:15.531703Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:15.917481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:16.384137Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:16.576481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:16.931914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:17.511611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:18.137623Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T15:23:30.966213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:32.063505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:32.283103Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:32.411246Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:32.581508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:33.872695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:33.993202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:34.030599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:34.559420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:35.749011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:36.564978Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:38.409463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:39.014493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:39.590897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:40.114055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:40.899434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:41.496560Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:41.775234Z | Info | Live bytes: 1192.44MB Heap size: 3143.63MB +2024-07-04T15:23:42.016857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:42.283877Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:42.604912Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:42.805323Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:42.812485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:42.963060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:43.492762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:44.227276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:45.611741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:46.720967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-04T15:23:47.244244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:56.336628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:23:57.407100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:01.262024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:02.324173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:03.862272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:04.509039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:05.539074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:07.405533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:09.540389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:24:10.115357Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T15:24:41.808374Z | Info | Live bytes: 1209.85MB Heap size: 3143.63MB +2024-07-04T15:25:41.827108Z | Info | Live bytes: 1209.85MB Heap size: 3143.63MB +2024-07-04T15:26:41.888633Z | Info | Live bytes: 1209.85MB Heap size: 3143.63MB +2024-07-04T15:27:01.395934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:03.450046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:06.957111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:40.413484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:41.412042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:41.890160Z | Info | Live bytes: 1214.98MB Heap size: 3143.63MB +2024-07-04T15:27:41.996158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:42.656277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:43.231541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:50.316598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:50.989923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:51.557951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:52.448395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:53.478940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:54.096003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:54.691881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:55.502148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:56.087525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:56.973903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:57.551534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:58.151035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:58.717135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:27:59.404442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:28:00.051120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:28:00.682250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:28:01.317489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:28:01.920689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:28:02.678349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:28:41.931139Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:29:41.976750Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:30:41.987601Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:31:42.006653Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:32:42.020988Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:33:42.036378Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:34:42.095550Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:35:42.156425Z | Info | Live bytes: 1223.51MB Heap size: 3143.63MB +2024-07-04T15:36:42.184713Z | Info | Live bytes: 1232.83MB Heap size: 3143.63MB +2024-07-04T15:37:42.232591Z | Info | Live bytes: 1237.64MB Heap size: 3143.63MB +2024-07-04T15:38:42.240829Z | Info | Live bytes: 1237.64MB Heap size: 3143.63MB +2024-07-04T15:39:42.301782Z | Info | Live bytes: 1237.64MB Heap size: 3143.63MB +2024-07-04T15:40:42.363626Z | Info | Live bytes: 1237.64MB Heap size: 3143.63MB +2024-07-04T15:41:42.425503Z | Info | Live bytes: 1237.64MB Heap size: 3143.63MB +2024-07-04T15:42:23.131442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:23.772728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:24.497315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:25.093195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:25.821761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:26.404437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:27.012021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:35.442135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:36.706248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:37.347914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:38.109572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:38.729270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:39.341626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:42.429648Z | Info | Live bytes: 1248.65MB Heap size: 3143.63MB +2024-07-04T15:42:50.355044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:50.940349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:52.447918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:53.067423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:53.747864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:54.456038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:55.062144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:55.637819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:56.282468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:57.150960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:57.894381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:58.495598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:59.288044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:42:59.855093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:43:00.491882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:43:01.123157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:43:01.793294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:43:03.086211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:43:03.113810Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-04T15:43:03.715900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:43:10.049692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:43:42.457045Z | Info | Live bytes: 1460.20MB Heap size: 3143.63MB +2024-07-04T15:44:05.698778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-04T15:44:42.484414Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:45:42.545422Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:46:42.606901Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:47:42.668479Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:48:42.729886Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:49:42.791326Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:50:42.852686Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:51:42.914183Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:52:42.928700Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:53:42.990019Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:54:43.051608Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:55:43.112875Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:56:43.148464Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:57:43.209628Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:58:43.270660Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T15:59:43.332031Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:00:43.358132Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:01:43.419389Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:02:43.428978Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:03:43.474001Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:04:43.485440Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:05:43.546659Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:06:43.600675Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:07:43.655828Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:08:43.698736Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:09:43.731612Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:10:43.776048Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:11:43.836533Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:12:43.849361Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:13:43.894332Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:14:43.955602Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:15:44.002095Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:16:44.062571Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:17:44.123573Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:18:44.184849Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:19:44.211827Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:20:44.217767Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:21:44.279132Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:22:44.336169Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:23:44.397529Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:24:44.458799Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:25:44.479505Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:26:44.540454Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:27:44.601637Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:28:44.662575Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:29:44.723587Z | Info | Live bytes: 1472.47MB Heap size: 3143.63MB +2024-07-04T16:29:54.227424Z | Error | Got EOF +2024-07-05 08:25:41.1240000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-05 08:25:41.1260000 [client] INFO Finding haskell-language-server +2024-07-05 08:25:41.1270000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:41.1290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:41.1460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-05 08:25:41.4240000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:41.4240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:41.4400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-05 08:25:41.7360000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:41.7370000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:41.7460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-05 08:25:42.0540000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:42.0540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:42.0680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-05 08:25:42.3150000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:42.3150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:42.3230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-05 08:25:42.3550000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:42.3550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:42.3630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-05 08:25:42.3900000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:42.3910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:42.3980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-05 08:25:42.4330000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-05 08:25:42.4900000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:42.4900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:42.5000000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-05 08:25:42.6970000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-05 08:25:42.6980000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-05 08:25:58.7880000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-05 08:25:58.8410000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-05 08:25:58.8410000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:58.8410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:58.8460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-05 08:25:58.9410000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:58.9410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:58.9460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-05 08:25:58.9610000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:58.9610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:58.9660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-05 08:25:58.9800000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:58.9810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:58.9850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-05 08:25:59.0010000 [client] INFO Checking for ghcup installation +2024-07-05 08:25:59.0010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 08:25:59.0070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-05 08:25:59.1120000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-05 08:25:59.1120000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-05 08:25:59.1120000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-05 08:25:59.1120000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-05 08:25:59.1120000 [client] INFO server environment variables: +2024-07-05 08:25:59.1130000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-05 08:25:59.1130000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-05 08:25:59.1130000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-05 08:25:59.1140000 [client] INFO Starting language server +2024-07-05T08:26:09.601577Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-05T08:26:09.603481Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-05T08:26:09.603987Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-05T08:26:09.608653Z | Info | Logging heap statistics every 60.00s +2024-07-05T08:26:09.617705Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-05T08:26:09.618175Z | Info | Starting server +2024-07-05T08:26:09.620156Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-05T08:26:09.745326Z | Info | Started LSP server in 0.13s +2024-07-05T08:26:11.431032Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-05T08:26:11.432052Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T08:26:11.925077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:11.925130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:13.035996Z | Info | Load cabal cradle using single file +2024-07-05T08:26:14.044773Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT30417-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T08:26:18.730720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:22.833962Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-f9d9bc04ee90af8e594e1c4bc7033fff72315b15 +2024-07-05T08:26:22.843454Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-05T08:26:48.293508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:48.914176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:54.159259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:55.424717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:26:55.555845Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:26:55.612715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:26:55.629276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:55.684005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:26:55.769415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:26:56.137943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:26:58.213590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:01.862523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:27:02.033350Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:27:02.199619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:27:02.307397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:02.386216Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:27:02.449975Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:27:02.607056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:27:02.824131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:02.976073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:27:05.900110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:06.751714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:07.455498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:09.612128Z | Info | Live bytes: 877.44MB Heap size: 2171.60MB +2024-07-05T08:27:15.623782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:16.142388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:18.628865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:33.428528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:27:35.493807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:28:09.645473Z | Info | Live bytes: 883.51MB Heap size: 2171.60MB +2024-07-05T08:29:09.705127Z | Info | Live bytes: 883.51MB Heap size: 2171.60MB +2024-07-05T08:29:26.647845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:28.125503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:30.803743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:30.911981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:30.954988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:31.193830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:31.485017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:31.595800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:31.798663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:31.948890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:32.585747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:32.639500Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:32.716186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:32.992577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:33.496419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:34.507351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:35.357683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:35.771614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:36.294121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:37.519877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:38.138738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:38.185937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:38.260892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:38.528264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:39.234794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:39.477970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:39.941988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:45.129930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:47.278884Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:47.847010Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:48.303924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:49.338181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:50.147681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:50.207216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:50.234644Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:56.677717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:57.499329Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:57.701508Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:57.853441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:57.966546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:57.983793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:29:58.458741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:29:58.586705Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:29:59.166277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:30:09.712170Z | Info | Live bytes: 734.17MB Heap size: 2659.19MB +2024-07-05T08:30:31.033513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:30:31.657869Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:30:32.220473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:08.642767Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:08.799497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:08.820263Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:08.876018Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:08.962973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:08.991610Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:09.338079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:09.577910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:09.712823Z | Info | Live bytes: 897.30MB Heap size: 2659.19MB +2024-07-05T08:31:09.713041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:09.827115Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:09.931737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:10.030513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:10.106424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:10.209396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:10.335438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:10.452330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:10.566569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:10.583390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:11.010980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:11.139277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:11.795781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:12.313466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:13.006168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:13.083763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:13.352341Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:13.467701Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:13.550720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:13.651559Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:13.701724Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:13.831900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:13.898770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:14.132152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:17.509661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:21.105216Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:21.170919Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:21.288294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:21.315178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:21.355578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:21.816925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:35.021625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:35.102773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:35.299892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:35.397864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:35.445533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:35.517356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:35.577685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:35.964977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:36.573932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:37.104530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:37.115030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:37.170961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:37.275988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:37.623287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:38.410677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:39.890374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:41.603301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:47.652664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:48.020571Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:48.188773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:48.373774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:48.471807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:48.502288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:48.601739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:48.650886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:49.042782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:49.623590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:50.389911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:31:50.746854Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:50.803546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:50.899273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:31:50.971326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:09.117157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:09.257060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:09.294361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:09.340686Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:09.388297Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:09.422852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:09.713453Z | Info | Live bytes: 1187.95MB Heap size: 2659.19MB +2024-07-05T08:32:09.719835Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:09.820509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:09.839079Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:09.945674Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:10.049941Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:10.186275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:10.306647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:10.400924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:10.421504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:10.497240Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:10.626301Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:10.961229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:11.469195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:11.487029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:11.968731Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:12.002541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:12.920883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:12.970665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:13.133349Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:13.237257Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:13.320759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:13.386838Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:32:13.449165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:13.847683Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:32:14.506032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:41.262970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:42.372048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:42.983594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:44.806272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:45.839185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:32:58.287292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:07.130068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:09.717192Z | Info | Live bytes: 708.24MB Heap size: 2991.59MB +2024-07-05T08:33:20.150137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:39.160692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:40.029891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:40.676430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:50.167622Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:33:50.282889Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:33:50.445361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:52.469977Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:33:52.748455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:33:59.541691Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:33:59.631488Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:33:59.791443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:33:59.901211Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:33:59.972136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:00.003841Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:34:00.068342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:34:00.503472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:03.010006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:04.720576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:34:04.873197Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:34:04.983565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:34:05.090078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:05.127268Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:34:05.669661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:05.864605Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:34:09.721261Z | Info | Live bytes: 732.43MB Heap size: 2991.59MB +2024-07-05T08:34:17.191816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:18.501878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:26.210083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:27.629927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:29.879768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:30.374665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:30.982386Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:34:31.228860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:38.114934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:38.726369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:40.389741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:41.096275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:34:57.021125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:05.307820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:08.537633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:08.663626Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:08.741260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:08.772038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:08.910481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:08.964025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.042096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.359788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:09.389384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.491030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.670132Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.722272Z | Info | Live bytes: 888.13MB Heap size: 2991.59MB +2024-07-05T08:35:09.738439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.856811Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.935849Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:09.937766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:10.177058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:10.288396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:10.395158Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:10.620326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:12.073440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:12.911635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:17.356515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:21.611814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:23.058865Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:23.189024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:23.191813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:23.260362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:23.347049Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:23.379162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:35:23.723173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:46.075450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:35:57.863416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:36:09.732120Z | Info | Live bytes: 1018.15MB Heap size: 2991.59MB +2024-07-05T08:37:09.743352Z | Info | Live bytes: 1018.15MB Heap size: 2991.59MB +2024-07-05T08:37:56.838688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:37:57.393822Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:57.491354Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:57.776268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:37:57.799381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:57.964025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:58.049019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:58.149573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:58.209578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:58.420086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:37:58.996862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:37:59.602145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:59.801807Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:59.886719Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:37:59.925595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:37:59.940313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:00.501649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:01.467293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:02.059220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:03.049686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:03.912751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:04.707411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:04.814465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:04.928077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:05.000764Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:05.081375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:05.152286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:05.991400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:09.748614Z | Info | Live bytes: 1036.41MB Heap size: 2991.59MB +2024-07-05T08:38:14.309247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:15.393870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:15.613938Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:15.743696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:15.858830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:15.916735Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:16.058100Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:16.398236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:16.764998Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:17.434542Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:38:17.496658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:43.282486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:43.845819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:44.572536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:46.640206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:46.711185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:47.160580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:47.236138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:47.684104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:48.315913Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:48.333535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:48.411014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:38:48.847248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:38:49.505943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:39:09.768386Z | Info | Live bytes: 1266.95MB Heap size: 2991.59MB +2024-07-05T08:39:39.689374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:40:09.800135Z | Info | Live bytes: 1266.95MB Heap size: 2991.59MB +2024-07-05T08:40:52.520901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:40:53.611405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:40:55.044459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:40:55.692070Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:40:56.023653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:40:56.971560Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:40:57.421514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:40:58.759683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:40:59.746660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:00.457246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:00.980657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:02.371881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:03.227311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:06.467972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:07.472825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:41:07.527069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:07.590711Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:41:08.032483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:08.471856Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:41:08.650768Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:41:08.927392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:09.579502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:09.802127Z | Info | Live bytes: 1286.39MB Heap size: 2991.59MB +2024-07-05T08:41:24.397954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:25.182276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:25.809746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:26.584538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:29.397669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:34.343996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:46.285747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:41:47.638109Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:42:07.267889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:07.438355Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:42:07.823640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:08.449907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:09.400316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:09.803112Z | Info | Live bytes: 1296.06MB Heap size: 2991.59MB +2024-07-05T08:42:09.982853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:10.501438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:10.994144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:11.523827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:11.926030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:42:11.971232Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:42:12.033627Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:42:12.077833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:13.030545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:13.772903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:42:14.451678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:43:09.853190Z | Info | Live bytes: 1314.67MB Heap size: 2991.59MB +2024-07-05T08:44:09.870387Z | Info | Live bytes: 1314.67MB Heap size: 2991.59MB +2024-07-05T08:45:08.382354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:08.978408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:09.871884Z | Info | Live bytes: 1303.59MB Heap size: 2991.59MB +2024-07-05T08:45:09.933350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:12.530797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:14.323867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:16.247095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:17.531348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:18.507451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:20.011206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:20.701654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:21.289162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:21.913839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:22.441715Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:22.731800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:22.781082Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:22.818983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:22.943026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:27.286055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:28.293717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:29.075990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:33.613299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:33.918986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:34.150719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:35.717368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:35.765546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:36.221834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:55.118340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:55.252691Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:55.404228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:55.468745Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:55.586010Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:55.641147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:55.790592Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:55.887451Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:55.988797Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:56.102665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:56.136316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:56.288585Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:56.753342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:57.280023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:57.403145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:57.413685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:57.484035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:57.593363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:58.046151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:58.453981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:45:58.463851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:58.974824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:45:59.648796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:00.220283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:00.436366Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:00.626046Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:00.739924Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:00.771619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:00.885109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:00.967813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:01.302711Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:46:01.359834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:01.987310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:08.476905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:09.444991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:09.592069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:09.685615Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:09.802967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:09.873746Z | Info | Live bytes: 912.24MB Heap size: 3088.06MB +2024-07-05T08:46:09.913519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:10.885271Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:11.361743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:11.922977Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:46:12.495397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:31.307771Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:46:31.404587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:40.297406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:40.390481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:46:40.795899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:41.269972Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:46:46.454342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:47.382214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:47.997419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:48.528482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:50.463832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:57.985047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:46:59.422837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:00.001778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:00.581153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:01.229153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:05.842831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:06.814586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:09.875077Z | Info | Live bytes: 1198.54MB Heap size: 3088.06MB +2024-07-05T08:47:09.932396Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:47:09.980569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:22.120666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:22.749979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:23.371665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:24.038000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:24.802918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:25.496842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:26.464746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:27.023006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:27.656600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:28.166851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:28.699499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:29.226461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:29.750708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:30.299833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:34.083005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:36.840032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:36.869044Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:47:37.411172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:39.750864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:41.646002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:42.329619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:57.667503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:47:57.708209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:47:58.094239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:58.700446Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:47:58.759351Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:47:59.048551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:47:59.268814Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:47:59.733682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:48:01.018046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:48:01.605826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:48:02.147509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:48:08.833572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:48:09.878085Z | Info | Live bytes: 834.97MB Heap size: 3088.06MB +2024-07-05T08:48:39.345514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:48:42.059292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:48:44.514930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:49:01.297937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:49:01.367174Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:49:01.482375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:49:01.714820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:49:04.940985Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:49:05.005340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:49:05.377675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:49:08.636858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:49:09.570902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:49:09.879115Z | Info | Live bytes: 840.05MB Heap size: 3088.06MB +2024-07-05T08:49:10.161771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:49:37.906743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:49:57.857518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:50:00.232773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:50:00.613703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:50:05.531516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:50:07.471802Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:50:09.641416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:50:09.880376Z | Info | Live bytes: 854.08MB Heap size: 3088.06MB +2024-07-05T08:51:09.885449Z | Info | Live bytes: 854.08MB Heap size: 3088.06MB +2024-07-05T08:51:39.643676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:01.963053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:02.631962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:09.889791Z | Info | Live bytes: 994.43MB Heap size: 3088.06MB +2024-07-05T08:52:10.722332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:24.124747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:24.642219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:24.709958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:24.773242Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:24.843588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:24.916446Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:24.988740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:25.048116Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:25.097224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:25.497294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:26.015532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:26.246052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:26.342389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:26.461428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:26.586083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:26.731770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:26.975140Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:27.032038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:27.731263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:28.499810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:29.461526Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:52:29.666022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:30.318450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:31.393844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:32.231789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:35.305163Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:35.473048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:35.560049Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:35.751285Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:35.758992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:35.977862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:36.027924Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:36.150287Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:36.438984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:38.264363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:38.699852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:38.708527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:38.761518Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:38.842398Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:39.220958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:41.724830Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:42.028583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:42.111958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:42.193128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:42.292242Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:42.553235Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:52:42.554150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:42.909698Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:52:43.316493Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:43.480926Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:43.542031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:43.604468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:43.691458Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:52:43.723887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:44.452399Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:52:59.288753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:05.570509Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:53:05.605784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:07.991191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:08.147879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:08.226471Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:08.300258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:08.338401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:08.382622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:08.879497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:08.987736Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:53:09.646071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:09.891143Z | Info | Live bytes: 1121.16MB Heap size: 3307.21MB +2024-07-05T08:53:11.554853Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:53:12.955668Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:53:16.530594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:18.392443Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:53:23.790093Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:23.896943Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:24.000616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:24.057185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:24.176109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:24.191685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:24.252073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:24.339725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:24.720258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:25.773563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:25.826131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:25.891829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:25.958069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:26.029261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:26.096982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:26.343101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:31.388238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:32.009786Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:32.135257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:32.140685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:32.202074Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:32.281381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:32.332808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:32.458695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:32.497083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:32.668435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:33.925311Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:34.014964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:34.119135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:34.761201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:35.305744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:36.101673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:36.614511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:36.839996Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:37.133423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:37.294760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:37.412525Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:37.632578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:37.683324Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:53:38.130420Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:38.228598Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:38.334314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:38.386319Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:38.467221Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:53:38.514260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:47.828035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:50.278251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:53:51.500064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:09.906437Z | Info | Live bytes: 1376.97MB Heap size: 3307.21MB +2024-07-05T08:54:17.122637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:18.231721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:18.802883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:19.475316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:19.545394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:19.670977Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:19.744806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:19.857073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:19.866931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:19.919356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:20.280006Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:20.387280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:20.433717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:20.483096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:20.763866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:20.885645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:20.923297Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:21.034700Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:21.202632Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:21.377973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:24.151417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:26.033661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:26.872897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:33.826382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:34.014818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:34.075083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:34.272579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:34.803197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:35.339010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:35.905621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:36.481060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:36.618831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:36.686162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:36.754080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:36.895461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:36.963134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:37.033353Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:37.134502Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:37.351010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:38.680474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:45.586701Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:46.099409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:46.628846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:47.161452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:48.245631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:48.478929Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:48.653261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:48.754666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:48.907126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:49.604787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:50.419294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:50.949162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:51.047937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:51.141861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:51.295038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:51.313872Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:52.275090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:53.097639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:53.852435Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:54.196844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:54.301247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:54.308171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:54.400324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:54.510332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:54:54.852889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:56.195742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:54:58.296372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:01.575115Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:55:03.279203Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:55:03.595714Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:55:04.334873Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:55:05.169101Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:05.279096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:05.398537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:05.982848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:06.188312Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:06.299133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:06.372434Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:06.508230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:06.521526Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:06.600357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:06.643674Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:06.747132Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:07.052929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:07.755109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:07.971694Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:55:09.243916Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:09.910042Z | Info | Live bytes: 1621.97MB Heap size: 3307.21MB +2024-07-05T08:55:10.962792Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:11.464011Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:12.520566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:12.752478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:12.845579Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:12.942065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:13.797380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:14.364456Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:14.934994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:14.965649Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:15.083624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:15.149638Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:15.284895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:15.343598Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:15.406119Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:15.518855Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:15.539725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:16.121148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:16.731751Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:16.793099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:18.246869Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:25.694318Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:26.212382Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:26.858803Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:27.059400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:27.168760Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:55:27.624092Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:27.819319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:29.030921Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:45.412017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:46.053507Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:46.245301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:46.710140Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:47.035369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:47.099693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:47.160160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:47.209521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:47.665271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:47.854065Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:48.240204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:48.243065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:48.845985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:49.581104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:50.389449Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:50.558070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:51.047496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:51.062069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:51.767271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:52.495507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:53.358031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:53.874904Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:54.563571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:55.156511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:55.752902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:56.152404Z | Info | class: Detected implemented methods for class "HasTextEnvelope": [] +2024-07-05T08:55:56.330497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:56.348038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:55:57.124878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:55:59.657573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:01.317246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:02.500695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:03.582345Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T08:56:04.119043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:09.912708Z | Info | Live bytes: 897.83MB Heap size: 3615.49MB +2024-07-05T08:56:10.646902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:11.183256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:11.709486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:12.675268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:15.334603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:17.845536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:19.275048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:20.181495Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T08:56:26.995271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:27.747144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:56:28.004591Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T08:57:09.936555Z | Info | Live bytes: 1020.24MB Heap size: 3615.49MB +2024-07-05T08:57:19.157961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:57:19.397044Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:57:19.577844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:20.088233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:25.215397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:27.295780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:27.900711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:27.942487Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:57:28.112560Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:57:28.174011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:57:28.559618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:31.300328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:32.657316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:34.498382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:35.285362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:42.309827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:44.297597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:57:50.044735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:03.894732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:05.528534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:05.845931Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:05.987058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:06.074556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:06.081324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:06.647125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:07.246119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:09.940104Z | Info | Live bytes: 1023.38MB Heap size: 3615.49MB +2024-07-05T08:58:11.750238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:12.744988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:12.870624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:12.901545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:12.971555Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:13.151176Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:13.204732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:13.918765Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:58:14.014446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:14.575962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:24.831359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:25.602045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:27.252769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:40.884998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:41.146642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:41.306503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:41.361347Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:41.397324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:41.953608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:42.793440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:44.007706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:45.640846Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:45.707386Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:45.787909Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:58:46.081777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:50.257748Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T08:58:50.267511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:53.505133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:58:59.175285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:03.534323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:09.941399Z | Info | Live bytes: 1240.54MB Heap size: 3615.49MB +2024-07-05T08:59:10.059411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:10.754190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:17.629514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:18.830998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:21.803597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:26.622234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:26.873802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:27.167315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:27.814582Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:27.902977Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:27.950400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:28.483986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:28.675694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:28.826250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:29.002359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:29.028443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:29.183994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:29.349307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:29.601198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:29.620157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:29.764250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:29.900748Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:30.037446Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:30.145936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:30.212118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:30.250739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:30.335018Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:30.411583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:30.508469Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T08:59:30.707237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:33.078292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:34.043511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:37.300801Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:59:46.818756Z | Info | class: Detected implemented methods for class "FromCBOR": [] +2024-07-05T08:59:50.160395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:50.756581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T08:59:51.324654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:09.942988Z | Info | Live bytes: 1256.03MB Heap size: 3615.49MB +2024-07-05T09:00:21.203813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:21.590163Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:21.710627Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:21.757370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:21.791349Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:22.251622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:22.839317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:23.371402Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:23.476933Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:23.498961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:23.583626Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:23.681191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:24.042367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:24.194782Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:24.341710Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:24.464978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:24.611646Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:24.651678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:25.295937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:25.804382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:54.417595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:54.875224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:54.932687Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:55.003566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:55.238517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:55.264073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:55.436729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:55.538016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:55.834682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:55.895924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:56.110420Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:56.416188Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:56.573287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:56.690431Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:00:57.152535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:00:59.610727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:00.913265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:01.558987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:03.730743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:01:03.905850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:01:03.983471Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:01:04.070737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:04.097455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:01:04.135312Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:01:04.591748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:09.949639Z | Info | Live bytes: 1291.02MB Heap size: 3615.49MB +2024-07-05T09:01:16.922262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:18.875387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:23.157272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:24.699470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:40.040529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:40.816865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:40.867813Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:01:41.524150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:54.701335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:01:54.902643Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:01:55.548839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:09.683922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:09.908224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:09.951520Z | Info | Live bytes: 1582.01MB Heap size: 3615.49MB +2024-07-05T09:02:10.091543Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:10.195065Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:10.296498Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:10.358139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:10.364443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:10.437935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:10.903341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:11.094421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:11.237026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:11.290262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:11.443903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:11.501563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:11.555788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:11.560942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:11.638682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:11.890794Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:02:12.118023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:22.576924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:29.092705Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:29.253377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:29.327803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:29.438801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:29.504136Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:29.570887Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:29.790451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:30.127893Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:30.255186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:30.303278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:30.959129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:30.964173Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:02:31.467374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:33.994301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:43.244320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:43.302377Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:02:50.653956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:50.743623Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:02:51.198400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:02:51.522661Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:03:09.970014Z | Info | Live bytes: 1046.29MB Heap size: 3681.55MB +2024-07-05T09:03:12.217819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:14.989041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:15.108025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:15.199592Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:15.450848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:15.982961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:16.587706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:17.188279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:17.210297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:17.276825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:17.372247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:17.453213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:17.686768Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:03:17.754426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:19.886775Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:03:19.891967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:20.420390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:34.400131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:35.850041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:03:35.986293Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:03:36.630818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:04:04.341333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:04:05.674203Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:04:06.357725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:04:07.298964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:04:08.101473Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:04:09.972718Z | Info | Live bytes: 890.39MB Heap size: 3681.55MB +2024-07-05T09:04:21.035363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:04:21.392694Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T09:05:10.017694Z | Info | Live bytes: 1076.49MB Heap size: 3681.55MB +2024-07-05T09:05:28.736315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:05:29.259179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:05:31.680626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:05:32.625886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:05:32.755869Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:05:39.036757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:05:42.021936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:10.026435Z | Info | Live bytes: 1320.02MB Heap size: 3681.55MB +2024-07-05T09:06:10.857127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:14.116750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:14.265917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:14.410089Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:14.473389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:14.480172Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:14.540346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:14.992750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:29.337922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:30.279683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:30.487998Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:30.639407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:30.718647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:06:30.947815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:31.892883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:34.431648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:39.573920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:46.282475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:06:47.497366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:07:10.032351Z | Info | Live bytes: 1324.03MB Heap size: 3681.55MB +2024-07-05T09:08:10.088715Z | Info | Live bytes: 1324.03MB Heap size: 3681.55MB +2024-07-05T09:08:38.175777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:08:38.689798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:08:38.770308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:08:38.788729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:08:51.831520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:08:54.389455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:08:55.084730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:08:57.968822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:09:01.458671Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:09:01.674409Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:09:01.751867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:09:02.289661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:09:02.413496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:09:02.480538Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:09:02.725200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:09:10.097688Z | Info | Live bytes: 1344.57MB Heap size: 3681.55MB +2024-07-05T09:09:40.075098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:09:42.681243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:09:43.734232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:09:44.355782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:09:45.009534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:00.816606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:01.798188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:04.310774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:10:04.750310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:05.347404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:05.923872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:06.940894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:07.020128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:10:07.090164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:10:07.226405Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:10:07.463873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:08.254870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:08.832668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:09.577682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:10.100232Z | Info | Live bytes: 1347.57MB Heap size: 3681.55MB +2024-07-05T09:10:15.500572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:10:15.917480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:16.521184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:17.075157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:19.915414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:20.443907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:37.622074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:38.333397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:39.122194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:40.753451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:41.408491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:42.918478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:43.454402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:43.959284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:48.224179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:49.957417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:10:49.999101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:58.972358Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:59.652309Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:10:59.757198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:10:59.926888Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:11:00.024494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:11:00.165131Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:11:00.231755Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:11:00.300194Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:11:00.380529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:11:00.423222Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:11:10.110644Z | Info | Live bytes: 1377.52MB Heap size: 3681.55MB +2024-07-05T09:12:10.171642Z | Info | Live bytes: 1377.52MB Heap size: 3681.55MB +2024-07-05T09:13:10.231102Z | Info | Live bytes: 1377.52MB Heap size: 3681.55MB +2024-07-05T09:14:10.292171Z | Info | Live bytes: 1377.52MB Heap size: 3681.55MB +2024-07-05T09:15:10.353285Z | Info | Live bytes: 1377.52MB Heap size: 3681.55MB +2024-07-05T09:16:10.414308Z | Info | Live bytes: 1377.52MB Heap size: 3681.55MB +2024-07-05T09:17:10.475101Z | Info | Live bytes: 1377.52MB Heap size: 3681.55MB +2024-07-05T09:17:15.704929Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:15.859274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:15.908780Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:16.121563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:16.137758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:17:16.225995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:16.303484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:16.685140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:17:23.395421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:17:23.904412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:17:39.524664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:17:54.454204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:54.552417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:17:54.816098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:18:10.491180Z | Info | Live bytes: 1388.92MB Heap size: 3681.55MB +2024-07-05T09:19:10.537203Z | Info | Live bytes: 1388.92MB Heap size: 3681.55MB +2024-07-05T09:19:13.943515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:19:14.506527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:19:15.078975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:19:16.030584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:19:17.451653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:19:18.029530Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T09:20:10.576376Z | Info | Live bytes: 1382.97MB Heap size: 3681.55MB +2024-07-05T09:21:10.637698Z | Info | Live bytes: 1382.97MB Heap size: 3681.55MB +2024-07-05T09:21:59.083080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:21:59.364055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:21:59.528642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:00.158365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:00.224096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:00.350194Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:00.407062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:00.557802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:00.628983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:00.670389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:00.704978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:00.782604Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:01.163589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:10.646529Z | Info | Live bytes: 1396.06MB Heap size: 3681.55MB +2024-07-05T09:22:33.176215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:33.800986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:38.490046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:39.732572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:44.770045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:44.958163Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:45.069316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:45.230228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:22:45.295754Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:45.612531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:22:45.776331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:23:00.803013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:23:01.491535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:23:02.083483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:23:10.652095Z | Info | Live bytes: 1696.28MB Heap size: 3681.55MB +2024-07-05T09:24:10.653632Z | Info | Live bytes: 1696.28MB Heap size: 3681.55MB +2024-07-05T09:25:10.714810Z | Info | Live bytes: 1696.28MB Heap size: 3681.55MB +2024-07-05T09:25:15.544230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:16.080186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:18.070713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:18.862616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:46.110317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:46.928669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:47.959070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:48.583616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:49.193369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:49.774815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:50.386471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:50.949807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:51.508022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:55.454927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:55.993937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:56.877386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:58.099840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:58.715932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:59.288666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:25:59.803628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:00.596375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:02.179552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:10.721134Z | Info | Live bytes: 851.99MB Heap size: 3681.55MB +2024-07-05T09:26:15.864049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:16.507160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:18.356134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:18.799470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:19.301547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:19.383335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:19.484064Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:19.843341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:20.340903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:20.850335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:21.857116Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:21.938538Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:21.994370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:22.236054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:22.731356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:23.552939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:24.149615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:25.358091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:25.868709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:26.444046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:28.005712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:28.520744Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:28.545143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:29.536793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:30.149771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:30.662466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:32.104962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:32.231674Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:32.356630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:32.386426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:32.422700Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:32.632993Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:33.078647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:33.234607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:33.682438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:37.474924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:41.321199Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:41.514428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:41.674978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:41.766285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:41.799737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:26:42.423657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:43.002131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:43.934769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:44.861364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:45.504871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:46.759318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:26:47.963144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:27:10.739296Z | Info | Live bytes: 897.39MB Heap size: 3681.55MB +2024-07-05T09:27:19.047637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:19.240105Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:19.433614Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:19.464752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:27:19.585054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:20.005102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:27:20.598614Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:20.684522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:20.923015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:27:21.475827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:21.803209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:21.887074Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:21.918425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:27:21.968992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:27:22.424114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:27:26.888771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:28:10.743484Z | Info | Live bytes: 902.14MB Heap size: 3681.55MB +2024-07-05T09:28:33.001560Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:33.147038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:33.269522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:33.405964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:33.419174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:28:33.472767Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:33.631358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:33.704379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:33.930191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:28:34.012632Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:34.070312Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:34.182727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:34.457086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:28:34.980550Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:35.119131Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:35.167698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:35.286552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:28:35.422863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:28:40.325231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:28:41.098218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:29:10.765410Z | Info | Live bytes: 910.19MB Heap size: 3681.55MB +2024-07-05T09:30:10.826028Z | Info | Live bytes: 910.19MB Heap size: 3681.55MB +2024-07-05T09:31:10.830427Z | Info | Live bytes: 910.19MB Heap size: 3681.55MB +2024-07-05T09:31:54.773661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:54.886015Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:55.080053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:55.230146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:31:55.353789Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:55.494216Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:55.814556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:31:57.803535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:31:58.358519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:58.432729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:31:58.536481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:58.997534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:31:59.004915Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:59.111053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:59.569802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:31:59.643600Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:59.744361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:59.859832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:31:59.910655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:00.096606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:00.285058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:00.504447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:00.749430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:03.213047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:10.839662Z | Info | Live bytes: 916.29MB Heap size: 3681.55MB +2024-07-05T09:32:16.934261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:17.434327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:17.928796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:18.179425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:18.250298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:18.550795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:20.648998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:21.323540Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:21.782970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:21.908619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:21.992315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:22.218078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:22.589023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:22.712809Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:22.751062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:22.818090Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:23.045891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:23.608751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:24.007122Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:24.095842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:24.168073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:24.552086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:24.658552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:24.690184Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:32:24.808832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:33.858754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:35.911641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:37.269546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:38.046417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:32:39.202373Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:32:39.338390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:33:10.857119Z | Info | Live bytes: 1228.28MB Heap size: 3681.55MB +2024-07-05T09:33:48.035562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:33:50.354920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:33:52.247730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:33:54.564327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:10.858857Z | Info | Live bytes: 1234.55MB Heap size: 3681.55MB +2024-07-05T09:34:11.207165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:12.237443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:12.869528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:13.368438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:14.234406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:15.690860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:20.021088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:20.396545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:20.520206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:20.666322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:20.737541Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:20.737841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:20.837294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:21.300899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:21.757037Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:21.854501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:21.942678Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:22.392755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:22.940524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:23.188979Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:23.641461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:24.969677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:26.018668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:26.617690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:27.153015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:35.030621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:35.218926Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:35.269839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:35.345682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:35.519836Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:35.796193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:36.306475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:36.500728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:36.549967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:36.728565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:36.828042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:37.272611Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:37.403756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:37.527951Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:37.723149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:38.209760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:38.656011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:39.230186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:39.771556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:41.181999Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:41.578908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:42.121897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:42.331413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:42.357483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:42.524964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:42.975075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:50.003268Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:50.168391Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:50.376103Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:50.452558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:51.475576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:52.100642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:52.216214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:52.291353Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:52.359370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:52.471272Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:34:52.667049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:34:53.308511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:01.817446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:02.368249Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:35:02.909510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:06.811878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:07.307279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:08.106534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:08.604453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:09.833494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:10.386780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:10.860111Z | Info | Live bytes: 1426.02MB Heap size: 3681.55MB +2024-07-05T09:35:11.017712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:11.762251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:11.863657Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:35:12.328183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:12.959134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:13.505240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:14.407184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:16.467686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:22.816589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:24.274451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:24.842343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:35:24.887552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:25.389865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:25.896498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:33.103612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:35:40.368128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:05.898955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:08.400944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:10.409385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:10.861778Z | Info | Live bytes: 1503.17MB Heap size: 3681.55MB +2024-07-05T09:36:14.215475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:15.767024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:17.885940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:20.373693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:36:20.441686Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:36:20.823675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:21.331532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:27.741683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:36:28.159080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:28.659357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:36:28.751609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:29.114753Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:36:29.226274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:36:29.317918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:36:29.480091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:36:35.382251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:04.101682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:04.373180Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:04.710212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:05.419670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:06.153417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:07.623158Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:07.744065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:08.223894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:08.497298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:08.677492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:08.760969Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:08.931053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:09.008576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:09.189426Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:09.209423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:09.731455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:09.815061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:10.015591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:10.863058Z | Info | Live bytes: 1517.67MB Heap size: 3681.55MB +2024-07-05T09:37:11.179909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:11.872086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:13.282892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:14.863916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:25.604456Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:44.438396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:47.168144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:49.303632Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:37:49.363928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:37:49.879541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:07.634777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:07.842477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:07.891357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:08.046482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:08.048536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:08.104259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:08.166306Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:08.294891Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:08.554094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:10.867221Z | Info | Live bytes: 1525.97MB Heap size: 3681.55MB +2024-07-05T09:38:14.895680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:15.085001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:15.473266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:16.235819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:16.297791Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:16.375593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:16.432873Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:38:16.735308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:42.808626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:43.345987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:38:54.285851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:10.569932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:10.869933Z | Info | Live bytes: 1565.71MB Heap size: 3681.55MB +2024-07-05T09:39:12.666259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:14.431281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:18.130616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:19.095855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:20.621278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:23.104855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:25.393343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:25.948514Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:39:38.991483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:39.704785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:40.206033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:41.779125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:43.085337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:45.006303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:46.781570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:54.720357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:55.463891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:55.859535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:39:56.033813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:56.592241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:56.969484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:39:57.048297Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:39:57.099012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:39:57.159226Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T09:39:57.600361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:40:04.915779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:40:05.511397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:40:06.837503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:40:07.431111Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:40:10.874179Z | Info | Live bytes: 1602.62MB Heap size: 3681.55MB +2024-07-05T09:40:40.459473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:40:50.628284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:40:51.164561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:41:10.884898Z | Info | Live bytes: 1593.52MB Heap size: 3681.55MB +2024-07-05T09:42:10.890134Z | Info | Live bytes: 1593.52MB Heap size: 3681.55MB +2024-07-05T09:42:14.508977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:42:15.724497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:42:21.447152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:42:27.790496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:42:42.184137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:43:05.818791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:43:06.742482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:43:07.659319Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T09:43:08.204002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T09:43:10.893781Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:44:10.954142Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:45:10.962114Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:46:11.022178Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:47:11.082667Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:48:11.143159Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:49:11.179191Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:50:11.235891Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:51:11.296691Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:52:11.331446Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:53:11.392209Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:54:11.449685Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:55:11.498158Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:56:11.558099Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:57:11.618737Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:58:11.672529Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T09:59:11.733078Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:00:11.755213Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:01:11.815053Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:02:11.875059Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:03:11.935270Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:04:11.995058Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:05:12.055032Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:06:12.082921Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:07:12.143186Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:08:12.204102Z | Info | Live bytes: 1613.81MB Heap size: 3681.55MB +2024-07-05T10:08:16.778707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:08:47.234005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:08:54.605642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:09:12.223477Z | Info | Live bytes: 1604.20MB Heap size: 3681.55MB +2024-07-05T10:09:46.779063Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T10:09:46.789651Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T10:09:47.169624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:09:47.171290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:09:58.984760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:09:59.718185Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T10:09:59.718481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:10:03.878480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:10:04.442485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:10:11.548314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:10:12.224584Z | Info | Live bytes: 1620.15MB Heap size: 3681.55MB +2024-07-05T10:10:15.522343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:10:17.664905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:10:20.584270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:10:21.314740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:11:12.277495Z | Info | Live bytes: 1623.95MB Heap size: 3681.55MB +2024-07-05T10:11:51.162344Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:11:51.590082Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:03.182100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:03.754311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:04.354356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:10.926820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:11.424106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:11.937068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:12.279156Z | Info | Live bytes: 1641.49MB Heap size: 3681.55MB +2024-07-05T10:12:12.449624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:13.057133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:13.654373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:20.013433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:20.957693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:21.867058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:22.264317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:12:22.320764Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:12:22.572641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:28.221418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:12:28.638070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:28.665279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:12:28.722272Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:12:28.805360Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:12:29.167972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:50.234894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:50.853080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:51.448980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:53.121869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:53.767899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:54.454671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:55.086532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:12:55.741133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:13:12.296728Z | Info | Live bytes: 1665.24MB Heap size: 3681.55MB +2024-07-05T10:14:01.172535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:07.591335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:12.301714Z | Info | Live bytes: 1698.29MB Heap size: 3681.55MB +2024-07-05T10:14:14.168060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:18.432559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:30.452545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:31.041613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:31.553423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:32.242187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:33.267803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:14:33.547235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:34.343779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:34.348550Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:14:34.420479Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:14:34.873431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:36.269515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:36.845093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:46.481738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:14:46.615025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:14:46.695699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:14:46.704345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:46.783000Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:14:47.237333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:14:59.990095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:00.637382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:01.244057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:12.314604Z | Info | Live bytes: 1003.41MB Heap size: 3681.55MB +2024-07-05T10:15:22.897408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:22.956847Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:23.129064Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:23.200607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:23.231777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:23.301407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:23.421495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:23.677903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:23.781221Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:23.899934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:24.020264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:24.124207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:24.188079Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:24.303712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:24.403104Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:24.553279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:24.651142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:24.695495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:25.117251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:25.160969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:25.216682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:25.280763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:25.697290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:26.203088Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:26.509679Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:26.679350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:26.771494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:27.248482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:27.528164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:28.009303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:28.557623Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:29.000262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:29.032838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:29.292895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:29.560411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:29.690523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:29.767003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:31.262147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:31.283111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:31.621013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:31.751917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:32.096540Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:32.942420Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:33.353399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:33.422543Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:34.003852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:34.251161Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:34.622040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:34.928481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:35.196092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:36.146546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:36.335123Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:36.474110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:46.052086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:46.173475Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:46.356411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:46.460581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:15:46.519044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:15:46.874405Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T10:15:47.540765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:16:12.335805Z | Info | Live bytes: 1666.03MB Heap size: 3681.55MB +2024-07-05T10:16:36.923148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:16:40.762273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:17:12.372489Z | Info | Live bytes: 1666.03MB Heap size: 3681.55MB +2024-07-05T10:18:12.424025Z | Info | Live bytes: 1666.03MB Heap size: 3681.55MB +2024-07-05T10:19:12.485362Z | Info | Live bytes: 1666.03MB Heap size: 3681.55MB +2024-07-05T10:20:12.546677Z | Info | Live bytes: 1666.03MB Heap size: 3681.55MB +2024-07-05T10:20:38.284793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:20:46.067879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:20:47.589356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:20:49.342936Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T10:21:12.557352Z | Info | Live bytes: 1667.27MB Heap size: 3681.55MB +2024-07-05T10:21:34.355098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:21:34.918692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:21:36.222478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:21:37.387253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:21:39.307960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:21:41.455861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:21:54.484106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:21:58.485269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:00.443556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:04.999804Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T10:22:06.141365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:12.561354Z | Info | Live bytes: 1464.84MB Heap size: 3735.03MB +2024-07-05T10:22:24.897750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:25.452814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:27.293780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:33.042833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:33.684346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:34.204251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:40.640912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:49.731445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:50.333632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:50.949161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:51.661593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:52.323657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:53.029239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:53.896273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:54.766094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:22:55.841786Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T10:23:12.574370Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:24:12.589764Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:25:12.627413Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:26:12.688177Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:27:12.698685Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:28:12.751160Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:29:12.797285Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:30:12.841223Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:31:12.902404Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:32:12.963774Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:33:13.024074Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:34:13.074625Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:35:13.135388Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:36:13.148310Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:37:13.209209Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:38:13.269956Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:39:13.330774Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:40:13.379290Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:41:13.440617Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:42:13.462943Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:43:13.522457Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:44:13.583775Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:45:13.634517Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:46:13.696064Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:47:13.757134Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:48:13.785722Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:49:13.847113Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:50:13.893536Z | Info | Live bytes: 1622.20MB Heap size: 3735.03MB +2024-07-05T10:51:01.013697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:51:13.902856Z | Info | Live bytes: 1714.90MB Heap size: 3735.03MB +2024-07-05T10:52:13.948192Z | Info | Live bytes: 1714.90MB Heap size: 3735.03MB +2024-07-05T10:53:13.957523Z | Info | Live bytes: 1714.90MB Heap size: 3735.03MB +2024-07-05T10:53:36.026825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:53:45.533616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:53:47.087098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:54:03.102537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:54:13.967585Z | Info | Live bytes: 1834.91MB Heap size: 3735.03MB +2024-07-05T10:54:20.057208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:54:24.546563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:54:29.851643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:54:31.739942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:54:59.511810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:02.152324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:04.836875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:05.425331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:07.713798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:08.238208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:10.985848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:11.948703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:13.971272Z | Info | Live bytes: 913.60MB Heap size: 3905.95MB +2024-07-05T10:55:20.532548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:21.900916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:23.289937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:26.478723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:38.527569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:39.186728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:39.689934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:40.427525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:41.970071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:52.581283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:55:56.080593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:07.598671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:08.355599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:11.182330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:11.708215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:12.978976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:13.754423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:13.972833Z | Info | Live bytes: 905.68MB Heap size: 3905.95MB +2024-07-05T10:56:37.162991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:56:37.308244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:56:37.447729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:56:37.568607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:56:37.571498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:37.679842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:56:38.127027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:38.482744Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T10:56:38.921018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:38.943169Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T10:56:40.482254Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T10:56:41.067430Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T10:56:41.777988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:41.907906Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T10:56:43.427699Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T10:56:46.758240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:56:47.577055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:57:00.033610Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T10:57:03.069739Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T10:57:11.117154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:57:13.977123Z | Info | Live bytes: 1050.47MB Heap size: 3905.95MB +2024-07-05T10:57:30.496654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:57:32.050361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:57:34.376902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:57:39.371039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:58:14.012617Z | Info | Live bytes: 1058.27MB Heap size: 3905.95MB +2024-07-05T10:58:18.313547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:58:22.081748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T10:59:14.066844Z | Info | Live bytes: 1058.27MB Heap size: 3905.95MB +2024-07-05T10:59:20.139674Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T10:59:20.211177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:14.116163Z | Info | Live bytes: 1212.02MB Heap size: 3905.95MB +2024-07-05T11:00:24.229765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:24.882242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:25.584266Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:00:25.786391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:26.689076Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:00:26.888401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:31.019072Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:00:32.398672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:34.777754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:35.205431Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:00:35.287256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:35.647614Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:00:35.833373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:45.271261Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:00:46.341803Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:00:47.099453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:47.314527Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:00:54.413095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:00:59.236283Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:01:00.518497Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:01:03.330468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:05.288363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:06.060509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:14.125431Z | Info | Live bytes: 1372.43MB Heap size: 3905.95MB +2024-07-05T11:01:18.270624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:23.492911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:36.793285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:42.815801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:43.947695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:01:43.970803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:05.772325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:06.268415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:07.616079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:08.358739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:14.133194Z | Info | Live bytes: 1376.30MB Heap size: 3905.95MB +2024-07-05T11:02:20.512374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:21.034871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:25.769855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:26.271566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:27.137776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:28.591766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:29.300962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:29.890756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:32.037038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:32.591599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:33.110169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:41.459066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:42.718747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:43.377326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:43.944435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:45.029266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:45.528487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:46.103961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:46.657874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:02:47.437334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:03.996152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:05.524567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:06.810832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:07.689713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:07.809779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:07.873636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:07.915227Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:07.977467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:08.006601Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:08.092262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:08.157361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:08.480912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:08.863684Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:03:09.034129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:14.134645Z | Info | Live bytes: 1694.64MB Heap size: 3905.95MB +2024-07-05T11:03:19.972222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:20.498846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:26.961855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:27.973306Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:28.061648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:28.098331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:28.398524Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:28.508870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:28.559340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:28.624473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:28.736477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:28.788902Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:29.087491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:29.728289Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:29.828365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:29.915607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:30.125759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:30.574503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:31.587631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:32.161466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:32.677588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:33.147659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:33.261430Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:33.312499Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:03:33.534849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:34.486783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:03:36.504275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:04:14.173388Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:05:14.218398Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:06:14.279624Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:07:14.313750Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:08:14.349389Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:09:14.410525Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:10:14.472089Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:11:14.524744Z | Info | Live bytes: 1718.84MB Heap size: 3905.95MB +2024-07-05T11:11:53.327881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:11:53.568838Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:11:53.744025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:11:54.017445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:11:54.096062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:11:54.143018Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:11:54.545055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:11:58.437213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:11:59.642298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:12:14.530518Z | Info | Live bytes: 1723.35MB Heap size: 3905.95MB +2024-07-05T11:12:17.651297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:12:18.625384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:14.561230Z | Info | Live bytes: 1723.56MB Heap size: 3905.95MB +2024-07-05T11:13:33.775934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:34.319284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:34.955327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:39.950499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:49.475180Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:13:49.859422Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:13:54.545818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:55.050639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:56.096418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:13:56.696327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:05.154708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:05.707230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:14:06.143492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:14.567609Z | Info | Live bytes: 1737.28MB Heap size: 3905.95MB +2024-07-05T11:14:32.305348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:36.072967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:37.799054Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:14:37.862512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:40.130006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:44.368827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:47.829576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:14:57.172312Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:14:57.704621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:15:07.678852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:15:07.735114Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:15:14.575084Z | Info | Live bytes: 1167.73MB Heap size: 3905.95MB +2024-07-05T11:15:34.889998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:15:50.203527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:16:14.600787Z | Info | Live bytes: 1177.66MB Heap size: 3905.95MB +2024-07-05T11:16:50.704967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:16:51.253813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:16:51.260322Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:16:56.978972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:16:57.513797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:17:03.098718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:17:13.124791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:17:14.602924Z | Info | Live bytes: 1176.10MB Heap size: 3905.95MB +2024-07-05T11:17:14.724447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:17:53.032231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:18:14.645867Z | Info | Live bytes: 1176.10MB Heap size: 3905.95MB +2024-07-05T11:18:18.103102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:19:14.704348Z | Info | Live bytes: 1176.10MB Heap size: 3905.95MB +2024-07-05T11:19:18.025509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:14.718269Z | Info | Live bytes: 1176.10MB Heap size: 3905.95MB +2024-07-05T11:20:15.330737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:15.902961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:18.726904Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:19.394872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:19.930085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:23.382385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:48.505473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:51.313927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:57.148326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:20:58.156344Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:20:58.677344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:00.089874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:10.051763Z | Info | class: Detected implemented methods for class "HasTypeProxy": [] +2024-07-05T11:21:10.589412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:14.724378Z | Info | Live bytes: 1208.16MB Heap size: 3905.95MB +2024-07-05T11:21:25.359134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:25.955762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:26.623130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:27.315360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:28.387288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:28.887897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:31.306256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:31.924916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:32.646773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:33.220572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:33.878678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:21:34.494855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:07.471972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:08.180371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:09.050995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:13.352019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:14.726797Z | Info | Live bytes: 1340.85MB Heap size: 3905.95MB +2024-07-05T11:22:17.169850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:21.435769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:22.506692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:26.237509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:28.441251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:22:28.851731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:29.382653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:22:29.827683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:30.344404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:30.969044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:31.469470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:31.965696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:32.528801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:33.060655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:34.174515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:34.697200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:35.310941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:35.843101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:52.143790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:52.652793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:52.968004Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:22:53.399545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:55.927802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:56.435798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:22:56.438755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:22:56.966888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:01.864813Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:23:01.902256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:06.043195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:07.563855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:10.126887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:10.297322Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:23:10.875237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:12.829086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:14.730174Z | Info | Live bytes: 1372.12MB Heap size: 3905.95MB +2024-07-05T11:23:15.985640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:23:16.281040Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T11:24:14.785069Z | Info | Live bytes: 1491.92MB Heap size: 3905.95MB +2024-07-05T11:25:14.846152Z | Info | Live bytes: 1491.92MB Heap size: 3905.95MB +2024-07-05T11:25:29.755373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:31.074840Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:31.224119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:31.349362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:31.809318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:35.950226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:38.724618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:41.932875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:43.754833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:44.711846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:45.241010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:47.444914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:47.931568Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:47.957882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:48.005601Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:48.181940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:48.360179Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:48.465663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:48.468725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:48.654275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:25:49.116974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:49.618959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:50.361724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:51.109060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:25:56.368525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:07.406464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:08.103932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:09.006696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:10.252456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:26:10.603105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:12.886078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:13.395307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:13.849085Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T11:26:14.168070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:26:14.848256Z | Info | Live bytes: 1670.92MB Heap size: 3905.95MB +2024-07-05T11:27:14.904881Z | Info | Live bytes: 1670.92MB Heap size: 3905.95MB +2024-07-05T11:28:14.966068Z | Info | Live bytes: 1670.92MB Heap size: 3905.95MB +2024-07-05T11:29:15.019172Z | Info | Live bytes: 1670.92MB Heap size: 3905.95MB +2024-07-05T11:30:15.080414Z | Info | Live bytes: 1670.92MB Heap size: 3905.95MB +2024-07-05T11:31:15.141266Z | Info | Live bytes: 1670.92MB Heap size: 3905.95MB +2024-07-05T11:31:30.349130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T11:32:15.182998Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:33:15.244546Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:34:15.246885Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:35:15.308068Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:36:15.337621Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:37:15.398311Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:38:15.427458Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:39:15.488298Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:40:15.500285Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:41:15.561099Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:42:15.579104Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:43:15.640140Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:44:15.684083Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:45:15.744258Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:46:15.749975Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:47:15.811007Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:48:15.871725Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:49:15.932420Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:50:15.993381Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:51:16.012476Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:52:16.073173Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:53:16.091203Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:54:16.152267Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:55:16.213646Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:56:16.274896Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:57:16.336107Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:58:16.341502Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T11:59:16.358760Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:00:16.419473Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:01:16.437670Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:02:16.490533Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:03:16.552091Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:04:16.613276Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:05:16.674400Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:06:16.702998Z | Info | Live bytes: 1687.77MB Heap size: 3905.95MB +2024-07-05T12:07:14.124504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:07:14.183167Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:07:14.573025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:07:15.142129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:07:15.742055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:07:16.705822Z | Info | Live bytes: 1679.86MB Heap size: 3905.95MB +2024-07-05T12:07:20.737713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:07:21.359429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:07:22.385798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:07:28.260434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:07:28.846774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:08:16.750207Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:09:16.811197Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:09:51.021547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:10:16.833827Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:11:16.895301Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:12:16.956431Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:13:17.017594Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:14:17.079220Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:14:48.046306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:17.102425Z | Info | Live bytes: 1682.54MB Heap size: 3905.95MB +2024-07-05T12:15:17.852623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:19.993741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:20.634408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:21.244642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:22.355568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:24.702984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:30.573258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:30.729944Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:30.877422Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:31.016534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:31.036910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:31.143150Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:31.210565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:31.580330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:31.586910Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:31.632828Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:31.761620Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:32.086186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:34.011884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:46.719068Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:46.819318Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:47.066874Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:47.147676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:47.320503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:47.440668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:47.514901Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:47.767238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:47.846904Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:47.941183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:48.095974Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:15:48.293554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:15:52.202454Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:15:52.257960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:17.123986Z | Info | Live bytes: 1830.91MB Heap size: 3905.95MB +2024-07-05T12:16:28.502358Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:38.628636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:39.316680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:41.725889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:45.838029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:47.410832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:47.970042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:48.714030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:53.893670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:54.475986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:55.227895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:55.758280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:56.745941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:57.242969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:16:58.386749Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:16:58.908510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:17:17.130344Z | Info | Live bytes: 1081.59MB Heap size: 3905.95MB +2024-07-05T12:18:17.187318Z | Info | Live bytes: 1081.59MB Heap size: 3905.95MB +2024-07-05T12:18:26.780902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:30.677390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:34.044694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:43.091631Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.245491Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.280357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:43.316444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.359741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.393596Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.644137Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.751536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.777341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:43.853712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:43.983136Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:44.129073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:44.314729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:44.828862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:45.429893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:45.569634Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:45.636441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:45.713274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:45.830640Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:46.019462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:46.722396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:46.804763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:47.156328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:47.207803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:47.299847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:47.340800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:47.440687Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:47.810200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:47.880482Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:18:48.532994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:51.854582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:56.237302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:56.316040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:56.381843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:56.446720Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:56.491083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:56.579503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:56.691001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:57.152629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:57.956473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:58.129364Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:58.267746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:58.447035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:58.656172Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:59.266959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:59.403478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:59.432088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:18:59.536121Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:59.666593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:18:59.793385Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:19:00.145310Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:19:00.370417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:19:00.604320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:06.786729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:07.571610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:08.715149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:19:08.770659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:19:09.031324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:09.873225Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:19:10.335300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:11.282102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:12.932900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:17.192923Z | Info | Live bytes: 1472.11MB Heap size: 3905.95MB +2024-07-05T12:19:29.673433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:32.306357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:33.090704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:33.715913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:34.751396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:35.474714Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:19:54.703325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:56.654902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:19:59.464730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:20:00.488870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:20:04.540096Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:20:17.206871Z | Info | Live bytes: 1465.23MB Heap size: 3905.95MB +2024-07-05T12:21:17.267180Z | Info | Live bytes: 1465.23MB Heap size: 3905.95MB +2024-07-05T12:21:30.315163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:30.688686Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:21:37.173882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:38.672380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:41.159387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:41.694054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:42.364461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:46.779229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:47.404322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:48.554919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:48.578594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:21:57.159847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:17.269278Z | Info | Live bytes: 1801.54MB Heap size: 3905.95MB +2024-07-05T12:22:26.049610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:30.184300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:31.039441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:31.853722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:32.978179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:37.462290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:38.115614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:38.765170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:56.450633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:22:59.927745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:23:01.500819Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:23:17.279370Z | Info | Live bytes: 1828.97MB Heap size: 3905.95MB +2024-07-05T12:24:17.341057Z | Info | Live bytes: 1828.97MB Heap size: 3905.95MB +2024-07-05T12:25:17.402242Z | Info | Live bytes: 1834.70MB Heap size: 3905.95MB +2024-07-05T12:25:28.496729Z | Info | Cradle path: cardano-api/src/Cardano/Api/Experimental.hs +2024-07-05T12:25:28.497104Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T12:25:28.551723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:25:33.976743Z | Info | Load cabal cradle using single file +2024-07-05T12:25:34.154591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:25:34.933609Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" +2024-07-05T12:25:35.055600Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT30417-526 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T12:25:36.981825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:25:37.585786Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" +2024-07-05T12:25:49.021493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:26:17.431099Z | Info | Live bytes: 1834.70MB Heap size: 3905.95MB +2024-07-05T12:26:56.091525Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-9dd16fdf9d4ec0d1009b9f04bf56cd11565229c2 +2024-07-05T12:26:56.091748Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-9dd16fdf9d4ec0d1009b9f04bf56cd11565229c2 +2024-07-05T12:26:56.097439Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-8.49.0.0-inplace + , cardano-api-8.49.0.0-inplace-internal ] +2024-07-05T12:27:17.447198Z | Info | Live bytes: 1427.56MB Heap size: 4065.33MB +2024-07-05T12:28:17.508433Z | Info | Live bytes: 1427.56MB Heap size: 4065.33MB +2024-07-05T12:28:27.333699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:28:31.806356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:28:35.499331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:28:38.150030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:28:38.741140Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:28:38.822940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:28:38.896054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:28:39.022170Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:28:39.089066Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:28:39.105347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:28:39.179867Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:28:39.270852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:28:39.643033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:28:40.107056Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs": [ ] +2024-07-05T12:28:40.281318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:29:17.546182Z | Info | Live bytes: 1567.04MB Heap size: 4065.33MB +2024-07-05T12:30:17.577895Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:31:17.639733Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:32:17.677695Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:33:17.722468Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:34:17.754625Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:35:17.815512Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:36:17.866842Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:37:17.872193Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:38:17.898361Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:39:17.959757Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:40:18.021225Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:41:18.058471Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:42:18.090529Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:43:18.152002Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:44:18.213423Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:45:18.274833Z | Info | Live bytes: 1563.31MB Heap size: 4065.33MB +2024-07-05T12:45:47.325463Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:47.373784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:45:47.476599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:47.541118Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:47.683588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:47.881036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:47.917571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:45:48.004091Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:48.259277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:48.456330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:45:48.466716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:45:49.034222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:45:50.133852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:45:51.300891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:45:57.522276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:09.293459Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:09.420429Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:09.542981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:09.744118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:10.194068Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:10.404443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:10.583408Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:10.650013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:10.669918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:10.890855Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:11.000987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:46:11.368398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:12.024979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:18.278090Z | Info | Live bytes: 1669.51MB Heap size: 4065.33MB +2024-07-05T12:46:22.141493Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs": [ ] +2024-07-05T12:46:43.402700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:45.432133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:46.656878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:48.208835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:49.624221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:53.944510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:54.511942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:55.663433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:46:56.382384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:47:18.299098Z | Info | Live bytes: 1675.55MB Heap size: 4065.33MB +2024-07-05T12:47:18.750792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:47:31.664864Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" ] +2024-07-05T12:47:58.942885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:47:59.070326Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs": [ ] +2024-07-05T12:47:59.070333Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:48:11.619736Z | Info | LSP: received shutdown +2024-07-05T12:48:11.622887Z | Error | Got EOF +2024-07-05T12:48:24.448225Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-05T12:48:24.449606Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-05T12:48:24.449872Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-05T12:48:24.452324Z | Info | Logging heap statistics every 60.00s +2024-07-05T12:48:24.459518Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-05T12:48:24.459890Z | Info | Starting server +2024-07-05T12:48:24.461350Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-05T12:48:24.501815Z | Info | Started LSP server in 0.04s +2024-07-05T12:48:25.737193Z | Info | Cradle path: cardano-api/src/Cardano/Api/Experimental.hs +2024-07-05T12:48:25.737836Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T12:48:26.238092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:48:27.174800Z | Info | Load cabal cradle using single file +2024-07-05T12:48:28.097055Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT329711-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T12:48:31.778783Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Scripts/New.hs +2024-07-05T12:48:31.779466Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T12:48:33.202041Z | Info | Load cabal cradle using single file +2024-07-05T12:48:34.137068Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT329711-1 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T12:48:34.733236Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/Version.hs +2024-07-05T12:48:34.733860Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T12:48:36.126345Z | Info | Load cabal cradle using single file +2024-07-05T12:48:37.079435Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT329711-2 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T12:48:37.699003Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-05T12:48:37.699695Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T12:48:39.124158Z | Info | Load cabal cradle using single file +2024-07-05T12:48:40.296013Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT329711-3 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T12:48:45.629728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:48:53.732172Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-05T12:48:53.732817Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T12:48:53.756449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:48:59.094968Z | Info | Load cabal cradle using single file +2024-07-05T12:49:00.252981Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT329711-4 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T12:49:02.445147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:07.908545Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-1615d6206a80f4a0e31ef63d6e69b655fd28231c +2024-07-05T12:49:07.912712Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-05T12:49:08.189622Z | Info | Cradle path: cardano-api/src/Cardano/Api/Experimental.hs +2024-07-05T12:49:08.190174Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T12:49:09.642058Z | Info | Load cabal cradle using single file +2024-07-05T12:49:10.561632Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT329711-5 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T12:49:19.899749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:24.453333Z | Info | Live bytes: 629.56MB Heap size: 2407.53MB +2024-07-05T12:49:31.500700Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:31.623670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:31.694142Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:31.761713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:31.880092Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:31.971557Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:32.084799Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:32.264803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:32.358773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:32.361034Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:32.781738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:32.848877Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:32.918879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:49:33.244453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:35.951669Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:49:35.973497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:46.215331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:47.495703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:49.320153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:50.200364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:51.431730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:54.152248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:56.117713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:56.929081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:57.822047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:49:59.143539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:50:00.584294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:50:02.331493Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:50:17.590367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:50:17.858062Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T12:50:18.512281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:50:24.454118Z | Info | Live bytes: 636.05MB Heap size: 2407.53MB +2024-07-05T12:51:05.897395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:51:07.029609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:51:11.715992Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" +2024-07-05T12:51:11.841510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:51:20.841638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:51:21.260671Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" +2024-07-05T12:51:21.449124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:51:24.458580Z | Info | Live bytes: 636.05MB Heap size: 2407.53MB +2024-07-05T12:51:49.514834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:51:50.913240Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" +2024-07-05T12:51:51.047066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:52:24.493590Z | Info | Live bytes: 636.05MB Heap size: 2407.53MB +2024-07-05T12:52:48.376228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:52:49.723894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:53:24.554900Z | Info | Live bytes: 636.05MB Heap size: 2407.53MB +2024-07-05T12:54:24.615411Z | Info | Live bytes: 636.05MB Heap size: 2407.53MB +2024-07-05T12:55:24.674455Z | Info | Live bytes: 636.05MB Heap size: 2407.53MB +2024-07-05T12:55:59.882157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:00.065653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:00.220075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:00.250803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:00.384313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:00.517952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:00.596492Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:00.717312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:00.926009Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:01.389677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:03.461063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:03.962519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:04.461280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:04.862906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:05.090687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:05.893186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:07.219815Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:56:07.748858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:14.679663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:14.752743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:14.955286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:15.082660Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:15.115592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:15.235625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:15.635994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:15.679197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:15.763260Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:16.216667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:16.792041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:18.582872Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:18.731168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:18.795759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:18.870485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:19.333508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:20.019184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:20.036059Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:20.129844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:56:20.587310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:21.176895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:22.175623Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:56:24.678449Z | Info | Live bytes: 637.29MB Heap size: 2407.53MB +2024-07-05T12:56:26.462982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:56:28.036140Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:56:28.225616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:24.593424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:24.680195Z | Info | Live bytes: 637.40MB Heap size: 2407.53MB +2024-07-05T12:57:27.143147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:28.401420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:28.919458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:56.652967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:57.220083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:57.933841Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:57:57.980492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:57:59.457734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:58:06.373935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:58:09.215711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:58:11.267202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:58:12.941574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:58:24.684511Z | Info | Live bytes: 644.16MB Heap size: 2407.53MB +2024-07-05T12:58:47.458709Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:58:47.463187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:58:48.009488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:58:53.162661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:04.868068Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:59:04.969075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:11.129392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:11.398124Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:59:18.459611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:18.725294Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:59:22.408011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:23.617089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:24.318303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:24.685986Z | Info | Live bytes: 644.15MB Heap size: 2407.53MB +2024-07-05T12:59:25.151022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:25.725134Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T12:59:44.160471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:45.063820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:46.937305Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:59:46.966193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:59:47.015623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:47.648520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:59:47.782931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:48.497670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:59:48.549355Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:59:48.645365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T12:59:48.954980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:50.341378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:51.254125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:51.760867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:53.103536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:55.102823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:55.750132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:56.406091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:56.925938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T12:59:57.884538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:15.665109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:15.844381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T13:00:16.251940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:16.757951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:17.320825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:17.843009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:18.442815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:19.818024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:20.870727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:21.581901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:22.093794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:22.699865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:23.276942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:23.825770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:24.610277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T13:00:24.687371Z | Info | Live bytes: 652.49MB Heap size: 2407.53MB +2024-07-05T13:00:24.821332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:25.745940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:26.442147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T13:00:26.494122Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T13:00:26.736257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:30.076991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:31.410682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:00:33.860671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:24.731096Z | Info | Live bytes: 653.53MB Heap size: 2407.53MB +2024-07-05T13:01:29.464212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:34.451539Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T13:01:34.737467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:40.183677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:49.753323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:50.250355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:50.766825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:51.612363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:52.371571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:53.017763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:01:53.527687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:02:24.758546Z | Info | Live bytes: 655.89MB Heap size: 2407.53MB +2024-07-05T13:03:24.778326Z | Info | Live bytes: 655.89MB Heap size: 2407.53MB +2024-07-05T13:04:24.783293Z | Info | Live bytes: 655.89MB Heap size: 2407.53MB +2024-07-05T13:04:25.197839Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-05T13:04:45.984621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:05:24.803991Z | Info | Live bytes: 713.94MB Heap size: 2407.53MB +2024-07-05T13:06:24.810419Z | Info | Live bytes: 713.94MB Heap size: 2407.53MB +2024-07-05T13:07:24.842357Z | Info | Live bytes: 713.94MB Heap size: 2407.53MB +2024-07-05T13:08:24.903231Z | Info | Live bytes: 713.94MB Heap size: 2407.53MB +2024-07-05T13:09:24.908033Z | Info | Live bytes: 713.94MB Heap size: 2407.53MB +2024-07-05T13:10:24.953611Z | Info | Live bytes: 713.94MB Heap size: 2407.53MB +2024-07-05T13:11:23.836231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:24.359915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:24.955125Z | Info | Live bytes: 719.89MB Heap size: 2407.53MB +2024-07-05T13:11:24.957927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:25.473999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:26.031767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:26.569188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:27.186351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:27.919437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:28.437124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:29.005578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:29.506633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:30.481347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:31.113907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:32.389804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:32.957568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:33.461255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:33.969044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:34.500379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:35.050292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:35.574502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:36.133257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:36.848523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:37.349685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:37.979916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:38.595864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:39.132167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:39.639310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:40.148180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:40.656242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:41.209747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:42.386289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:42.880875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:43.473897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:43.985336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:44.556086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:45.134955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:45.703642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:46.205488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:46.729770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:11:47.270851Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T13:12:05.523287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:06.094509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:06.607000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:07.125837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:07.695207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:08.302542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:09.390577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:09.946409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:10.468777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:11.834836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:12.480047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:13.158895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:13.684065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:14.445330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:15.010764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:16.771712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:17.563714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:19.302384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:24.387056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:24.956353Z | Info | Live bytes: 752.95MB Heap size: 2407.53MB +2024-07-05T13:12:25.217622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:26.412349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:27.019252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:27.552510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:27.991272Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T13:12:28.123737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:12:28.665306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T13:13:24.971261Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:14:25.015687Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:15:25.076480Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:16:25.137236Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:17:25.148565Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:18:25.186848Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:19:25.212115Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:20:25.272153Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:21:25.318273Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:22:25.378312Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:23:25.438751Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:24:25.499198Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:25:25.560422Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:26:25.621115Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:27:25.674486Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:28:25.735602Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:29:25.796352Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:30:25.857290Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:31:25.917154Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:32:25.978121Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:33:26.034262Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:34:26.049111Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:35:26.110610Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:36:26.171907Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:37:26.233546Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:38:26.276716Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:39:26.338311Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:40:26.390004Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:41:26.451214Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:42:26.479838Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:43:26.506421Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:44:26.567838Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:45:26.586390Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:46:26.647731Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:47:26.709059Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:48:26.770526Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:49:26.832150Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:54:04.757166Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:55:04.818364Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:56:04.879953Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:57:04.941843Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:58:04.968391Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T13:59:05.029680Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:00:05.036859Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:01:05.098670Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:02:05.160136Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:03:05.221501Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:04:05.282653Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:05:05.344057Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:06:05.381672Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:07:05.442638Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:08:05.502578Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:09:05.529301Z | Info | Live bytes: 767.04MB Heap size: 2407.53MB +2024-07-05T14:09:36.297340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:37.208642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:38.497403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:42.720075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:43.279473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:44.605976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:46.328047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:47.551659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:48.876173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:09:51.558513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:01.486443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:02.007003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:02.551482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:03.117283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:03.691007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:04.499248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:04.999948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:05.530178Z | Info | Live bytes: 767.91MB Heap size: 2407.53MB +2024-07-05T14:10:05.883635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:06.440378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:07.958745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:08.471170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:09.229411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:10.372081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:10.936231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:11.540583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:12.234708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:12.980571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:13.526668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:10:14.224528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:11:05.543588Z | Info | Live bytes: 784.79MB Heap size: 2407.53MB +2024-07-05T14:12:05.557616Z | Info | Live bytes: 784.79MB Heap size: 2407.53MB +2024-07-05T14:12:38.252296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:12:38.797223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:12:39.633734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:12:40.199360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:12:40.827943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:12:59.073366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:02.121270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:03.078660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:05.561616Z | Info | Live bytes: 778.93MB Heap size: 2407.53MB +2024-07-05T14:13:24.713036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:28.873897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:29.493367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:30.125474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:30.848545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:32.056635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:37.112567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:39.047773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:13:40.500331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:14:05.583724Z | Info | Live bytes: 782.53MB Heap size: 2407.53MB +2024-07-05T14:15:05.644714Z | Info | Live bytes: 782.53MB Heap size: 2407.53MB +2024-07-05T14:16:05.685450Z | Info | Live bytes: 782.53MB Heap size: 2407.53MB +2024-07-05T14:17:04.372451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:17:05.688172Z | Info | Live bytes: 782.53MB Heap size: 2407.53MB +2024-07-05T14:18:05.708654Z | Info | Live bytes: 782.53MB Heap size: 2407.53MB +2024-07-05T14:19:05.710113Z | Info | Live bytes: 797.51MB Heap size: 2407.53MB +2024-07-05T14:19:05.766588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:05.766593Z | Info | Live bytes: 797.51MB Heap size: 2407.53MB +2024-07-05T14:20:37.836907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:38.489447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:39.014283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:40.153952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:40.669717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:41.498100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:42.072273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:42.644249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:43.309437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:43.861600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:44.566861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:45.171285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:45.685322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:48.145874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:48.667853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:49.199794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:49.696576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:50.338929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:50.924310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:53.693292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:54.247035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:55.049345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:20:58.432711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:01.973768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:03.870353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:05.405799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:05.768390Z | Info | Live bytes: 809.31MB Heap size: 2407.53MB +2024-07-05T14:21:20.288953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:20.782307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:26.092698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:26.683352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:27.830482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:28.473734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:29.015437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:33.376494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:51.889311Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:21:52.037955Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:21:52.223372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:52.756916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:21:56.902215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:22:00.477642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:22:00.618655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:22:01.017520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:22:05.773311Z | Info | Live bytes: 825.29MB Heap size: 2407.53MB +2024-07-05T14:22:18.726163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:22:19.264533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:23:05.779895Z | Info | Live bytes: 819.34MB Heap size: 2407.53MB +2024-07-05T14:23:40.192952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:23:40.767560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:23:42.091029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:23:45.698039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:24:00.348572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:24:00.473159Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:24:01.947782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:24:05.785790Z | Info | Live bytes: 818.07MB Heap size: 2419.06MB +2024-07-05T14:24:45.811352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:24:46.340886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:24:46.867355Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:24:47.448241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:01.673094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:01.756032Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:01.846133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:01.971580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:04.530822Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:04.666530Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:04.785012Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:04.795977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:04.923013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:05.382396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:05.787567Z | Info | Live bytes: 836.14MB Heap size: 2419.06MB +2024-07-05T14:25:06.632761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:06.710625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:06.860007Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:06.888721Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:07.001973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:25:07.090304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:07.582962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:08.229473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:08.865666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:09.485086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:10.481640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:11.059421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:11.600324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:12.148101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:15.677121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:18.843533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:27.755816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:33.823383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:34.317804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:34.841982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:35.511362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:36.480546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:37.759966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:57.456023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:58.001170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:58.519302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:59.111296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:25:59.650429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:00.462802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:01.465453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:04.753937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:05.371751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:05.788440Z | Info | Live bytes: 861.55MB Heap size: 2486.17MB +2024-07-05T14:26:05.941420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:06.820834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:29.125065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:40.068386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:48.949249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:53.213433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:55.790919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:26:56.954869Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:26:57.486992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:05.797259Z | Info | Live bytes: 861.87MB Heap size: 2486.17MB +2024-07-05T14:27:24.505592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:25.095326Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:25.174901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:25.223456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:25.324732Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:25.414251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:25.677868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:26.439746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:26.754288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:27.012590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:27.202259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:27.258520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:27.533225Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:27.709941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:29.076949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:31.196117Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:31.373474Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:31.641079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:33.542659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:34.205070Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:34.432741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:34.654577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:34.671394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:27:35.186928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:39.054602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:40.779222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:41.366222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:42.009903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:42.609707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:43.116754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:43.712126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:44.312323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:27:45.033599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:02.241601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:05.800336Z | Info | Live bytes: 875.13MB Heap size: 2504.00MB +2024-07-05T14:28:07.434320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:13.530002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:16.448112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:18.700253Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:19.018540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:19.156696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:22.329254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:32.800660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:33.398182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:38.309461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:38.448387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:38.480706Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:38.563510Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:38.726501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:38.942400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:39.179497Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:39.314241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:39.365153Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:39.496152Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:39.523018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:39.866403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:40.103528Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:40.217686Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:40.295650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:40.349838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:41.119751Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:41.195340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:41.321781Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:41.415305Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:41.477908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:41.518439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:41.598493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:42.348776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:42.518216Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:42.791116Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:42.955883Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:42.970612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:43.049748Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:28:43.528395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:28:43.567591Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:28:44.229576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:29:04.625830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:29:05.527743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:29:05.801885Z | Info | Live bytes: 1005.84MB Heap size: 2536.51MB +2024-07-05T14:29:06.150215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:29:09.796307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:29:12.801793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:29:22.839911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:30:05.841702Z | Info | Live bytes: 1013.50MB Heap size: 2561.67MB +2024-07-05T14:30:57.461550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:30:57.686086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:30:58.133056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:30:58.796670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:30:58.866951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:30:58.936500Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:30:59.390334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:30:59.977483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:00.508808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:01.018643Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:01.168685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:01.261785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:01.781548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:05.847239Z | Info | Live bytes: 1047.62MB Heap size: 2571.11MB +2024-07-05T14:31:30.823420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:31.406273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:32.804343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:33.665526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:34.029761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:34.255624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:34.476122Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:35.282949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:36.067351Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:36.146703Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:36.289068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:36.315210Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:36.434145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:36.560911Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:36.613161Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:31:36.881524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:37.377355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:54.452664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:31:55.596716Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:31:56.149855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:32:05.857531Z | Info | Live bytes: 1044.54MB Heap size: 2603.61MB +2024-07-05T14:32:52.439698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:52.637691Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:52.819460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:52.869544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:32:52.949019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:53.088936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:53.148145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:53.397166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:32:54.718353Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:54.850331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:54.918771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:55.012408Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:55.166455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:32:56.599179Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:56.760377Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:56.877107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:56.971212Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:57.038951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:32:57.244164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:57.373729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:57.561244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:57.686659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:32:57.710238Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:57.766477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:57.871574Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:32:58.213490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:32:59.866104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:00.873067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:05.858956Z | Info | Live bytes: 1058.18MB Heap size: 2603.61MB +2024-07-05T14:33:11.746827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:11.910038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:11.936814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:11.989945Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:12.042237Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:12.082123Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:12.449908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:12.577562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:12.705761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:12.800646Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:12.906591Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:13.032696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:13.076427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:13.175520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:13.319572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:13.389656Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:13.513122Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:13.541354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:14.077095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:14.323295Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:14.559096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:14.587419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:14.709052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:14.817864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:14.907184Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:14.992765Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:15.186731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:15.793694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:15.894434Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:16.019968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:16.144695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:16.269253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:16.474011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:16.611572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:16.786466Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:16.872847Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:16.945595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:16.958317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:17.020170Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:33:17.417446Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:33:17.438533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:18.094453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:29.300670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:33:29.796695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:05.869489Z | Info | Live bytes: 1168.01MB Heap size: 2656.04MB +2024-07-05T14:34:07.498729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:09.142379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:09.289868Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:09.443673Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:09.486089Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:09.580892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:10.254291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:10.854361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:12.103612Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:12.168800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:12.584215Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:12.842077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:13.644863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:14.255379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:14.754700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:15.226119Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:15.317530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:15.863433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:15.978113Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:16.368840Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:16.421868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:16.520177Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:16.682214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:16.748024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:16.808231Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:16.900006Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:16.970755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:18.153664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:18.676963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:19.745517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:20.529478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:23.870438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:23.955368Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:24.115390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:24.185536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:24.299406Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:24.308185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:34:24.342723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:34:24.877161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:05.905531Z | Info | Live bytes: 1214.56MB Heap size: 2724.20MB +2024-07-05T14:35:09.298005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:12.871912Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:35:13.003814Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:35:13.119284Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:35:13.330419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:13.989077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:14.663801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:15.209276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:15.807848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:16.469401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:35:16.586537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:35:17.410209Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:35:17.478015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:02.039603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:02.641413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:03.322974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:03.535970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:36:03.856878Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:36:03.984354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:04.557275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:05.908233Z | Info | Live bytes: 736.87MB Heap size: 2895.12MB +2024-07-05T14:36:06.267455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:36:06.412302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:36:06.617483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:36:06.680478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:07.357555Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:07.717696Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:36:08.375448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:21.524168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:22.187939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:22.694395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:23.242894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:24.146439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:25.156536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:25.940342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:31.888325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:32.423076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:33.082932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:34.800278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:36:35.123295Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:36:39.180099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:37:05.931806Z | Info | Live bytes: 871.29MB Heap size: 2895.12MB +2024-07-05T14:38:05.933771Z | Info | Live bytes: 871.29MB Heap size: 2895.12MB +2024-07-05T14:38:57.337604Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:38:57.902915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:38:59.742473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:00.417748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:00.953373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:01.503558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:02.001753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:04.612565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:05.936368Z | Info | Live bytes: 884.40MB Heap size: 2895.12MB +2024-07-05T14:39:06.503051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:12.701389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:13.383661Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:39:19.075898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:22.824284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:31.212705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:31.807631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:32.623068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:32.762162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:39:33.160052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:33.689278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:34.181958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:39:34.368552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:39:34.570456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:39:34.611954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:34.707490Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:39:34.804434Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:39:34.872566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:39:35.141290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:39:35.696173Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:40:01.180485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:40:01.826097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:40:05.941746Z | Info | Live bytes: 932.17MB Heap size: 2895.12MB +2024-07-05T14:40:14.427428Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:41:05.965765Z | Info | Live bytes: 932.17MB Heap size: 2895.12MB +2024-07-05T14:41:39.227654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:41:39.392689Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:41:39.715125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:41:39.751435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:41:39.910201Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:41:40.051879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:41:40.158803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:41:40.247696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:41:40.351415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:41:40.363074Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:41:50.713847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:05.977675Z | Info | Live bytes: 949.16MB Heap size: 2895.12MB +2024-07-05T14:42:18.185312Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:42:25.264318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:25.404219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:25.589141Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:25.695694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:25.837531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:25.844915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:25.931304Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:26.377851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:27.020560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:27.196858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:27.275895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:27.631790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:27.633011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:27.782365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:28.220443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:28.854797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:29.587409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:31.786508Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:31.898556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:31.961306Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:31.977378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:33.042319Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:33.217847Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:33.344761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:42:33.484585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:34.047293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:34.561838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:42:59.644761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:00.201258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:01.341517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:02.069942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:05.984084Z | Info | Live bytes: 978.07MB Heap size: 2895.12MB +2024-07-05T14:43:06.698273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:07.484624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:21.747485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:23.117630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:43:23.157608Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:43:23.385089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:24.302984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:24.838547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:25.441621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:25.959043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:26.508470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:28.509861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:29.725889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:32.308379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:35.214952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:36.031610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:38.463955Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:43:42.810774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:43.456870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:43:43.920124Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:43:58.327973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:00.267799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:00.992317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:04.803353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:05.442080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:05.986937Z | Info | Live bytes: 984.13MB Heap size: 2895.12MB +2024-07-05T14:44:08.811089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:09.426854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:09.922413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:10.588763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:12.307413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:12.860107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:14.183700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:21.362145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:21.760202Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:44:24.572865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:39.473414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:42.180054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:42.896040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:43.437675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:48.583309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:44:51.712878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:45:02.263285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:45:02.783813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:45:05.992306Z | Info | Live bytes: 1007.28MB Heap size: 2895.12MB +2024-07-05T14:45:07.147090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:45:07.727643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:45:27.293927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:45:30.568018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:45:30.734543Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:45:31.393548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:06.027980Z | Info | Live bytes: 1007.13MB Heap size: 2895.12MB +2024-07-05T14:46:17.452072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:22.530512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:24.699947Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:24.779213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:24.869812Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:24.988918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:25.145811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:25.426545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:25.716829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:25.819789Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:25.884215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:25.918399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:26.198555Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:26.377080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:26.550265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:26.748524Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:26.832371Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:26.940586Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:27.003125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:27.218559Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:27.485265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:27.673080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:27.713395Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:27.834389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:27.909865Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:27.981569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:28.171185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:37.845658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:43.238134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:43.961774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:44.949218Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:45.175629Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:45.317063Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:45.393841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:48.486666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:48.792725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:50.522104Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:50.698798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:50.736914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:52.104939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:52.400934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:54.178452Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:54.330218Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:54.371653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:55.893922Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:56.355643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:56.413307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:56.872808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:57.381788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:57.724748Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:58.078261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:58.186477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:58.357298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:58.539174Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:58.688914Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:46:58.824055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:46:59.374727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:03.605214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:03.709222Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:03.846516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:03.972435Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:04.023124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:04.064921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:04.164332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:04.616985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:05.233985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:06.030540Z | Info | Live bytes: 1041.60MB Heap size: 2895.12MB +2024-07-05T14:47:11.620664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:11.623848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:14.871202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:15.032942Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:15.305996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:15.809046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:16.457600Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:47:33.011349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:33.948672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:34.449551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:34.796969Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:47:34.887181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:35.619553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:36.836113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:37.634122Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:38.129254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:38.678567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:47:39.262514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:06.053487Z | Info | Live bytes: 1059.89MB Heap size: 2895.12MB +2024-07-05T14:48:49.871345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:50.226765Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:48:50.358649Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:48:50.669751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:51.405339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:54.199078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:55.232805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:55.792276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:56.409854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:57.034179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:57.586977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:58.085489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:58.632324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:59.419284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:48:59.929681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:03.055591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:03.592307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:04.090867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:04.616951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:05.839216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:06.055433Z | Info | Live bytes: 1096.87MB Heap size: 2895.12MB +2024-07-05T14:49:06.694825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:07.396759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:08.181932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:08.709142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:09.242378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:09.775384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:10.311921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:10.854388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:11.548518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:12.224760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:12.717862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:13.448851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:13.950691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:14.818298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:15.450088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:16.083353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:16.665097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:18.011096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:18.124741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:49:18.580056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:18.596667Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:49:19.267871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:45.942495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:49:46.922291Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:50:04.643260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:50:05.458138Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:50:05.458862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:50:06.057133Z | Info | Live bytes: 1121.22MB Heap size: 2895.12MB +2024-07-05T14:50:55.744530Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:50:55.967844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:50:56.515911Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:50:56.917069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:50:56.962071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:50:57.425197Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:50:57.873151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:50:58.407160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:06.059380Z | Info | Live bytes: 1118.60MB Heap size: 2895.12MB +2024-07-05T14:51:10.921913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:11.516816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:12.045233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:14.808646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:15.703126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:16.632009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:19.743977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:20.322256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:24.008603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:36.309916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:46.055567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:46.854403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:47.513176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:48.039499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:48.582380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:49.304421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:49.853911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:51:50.012054Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:52:06.075713Z | Info | Live bytes: 1137.38MB Heap size: 2895.12MB +2024-07-05T14:52:57.844691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:52:59.119398Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:52:59.156972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:53:06.083327Z | Info | Live bytes: 1151.67MB Heap size: 2895.12MB +2024-07-05T14:53:13.936274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:53:14.316352Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:53:39.288964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:53:39.989459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:53:45.799052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:53:47.417746Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:54:06.102429Z | Info | Live bytes: 1161.78MB Heap size: 2895.12MB +2024-07-05T14:54:15.232553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:15.826887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:16.490784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:18.826437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:19.118343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:19.242029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:19.404536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:19.551159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:20.046339Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:20.295801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:20.477302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:20.492276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:20.543781Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:20.727790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:20.787832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:20.914214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:21.076263Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:21.132879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:21.172588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:21.985095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:22.747867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:23.582109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:23.652572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:23.939112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:24.036272Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:24.316407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:24.385881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:25.081345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:25.651148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:26.151056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:26.513774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:26.595224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:26.689317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:26.825173Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:26.971276Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:27.129770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:27.141545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:27.823041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:29.451279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:29.693920Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:54:30.134127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:30.899163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:31.535294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:32.106941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:32.764623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:33.349727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:36.691709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:37.198884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:41.304587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:45.344331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:46.164919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:47.325582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:47.959499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:48.568289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:49.075591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:51.691080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:53.819785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:54.376342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:57.238516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:57.779145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:54:58.475446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:55:02.785161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:55:03.111427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:55:03.173936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:55:03.265716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:55:03.331596Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:55:03.401152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:55:04.008186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:55:04.502674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:55:06.105401Z | Info | Live bytes: 1204.16MB Heap size: 2895.12MB +2024-07-05T14:56:06.109716Z | Info | Live bytes: 1204.16MB Heap size: 2895.12MB +2024-07-05T14:56:07.956047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:09.000469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:09.624832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:11.140777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:13.240696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:13.848869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:14.914490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:19.339932Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:56:19.666954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:27.567226Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:56:27.761277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:56:27.997541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:29.253511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:38.906882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:42.155264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:43.876672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:44.749438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:51.333626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:52.006671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:56:55.738762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:00.907638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:06.116010Z | Info | Live bytes: 1219.52MB Heap size: 2895.12MB +2024-07-05T14:57:17.926223Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:57:18.160207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:20.266831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:57:20.336727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:57:20.697963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:23.790383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:26.048612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:27.302904Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:29.382992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:30.847172Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:57:31.269145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:36.110767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:38.422795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:39.097791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:40.073689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:41.433771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:57:42.135723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:06.117154Z | Info | Live bytes: 1236.01MB Heap size: 2895.12MB +2024-07-05T14:58:11.766830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:13.147164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:58:13.224793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:58:13.570007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:13.916832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T14:58:14.351333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:15.034301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:19.095128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:19.853898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:24.846274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:27.325909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:27.874276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:29.509846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:58:29.722403Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T14:58:30.389801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T14:59:06.133798Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:00:06.195650Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:01:06.257342Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:02:06.318865Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:03:06.349701Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:04:06.411325Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:05:06.413641Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:06:06.458251Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:07:06.487920Z | Info | Live bytes: 668.05MB Heap size: 2996.83MB +2024-07-05T15:07:16.330617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:07:47.074728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:06.509013Z | Info | Live bytes: 678.61MB Heap size: 2996.83MB +2024-07-05T15:08:14.327086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:14.967574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:16.730086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:16.874293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:16.977024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:17.054481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:17.224968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:17.319971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:17.440530Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:17.868931Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:17.885883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:18.375915Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:18.724882Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:08:18.824992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:19.410914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:24.304112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:25.032357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:26.002996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:30.873609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:32.128244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:34.156675Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:08:37.429872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:38.448533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:40.692823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:40.959165Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:08:53.177288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:53.873898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:54.372257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:54.908974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:58.380306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:58.940932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:08:59.976412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:00.474876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:01.219819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:01.797826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:02.466866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:03.393309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:04.093231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:04.920885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:05.492942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:06.086641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:06.510412Z | Info | Live bytes: 686.62MB Heap size: 2996.83MB +2024-07-05T15:09:06.618964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:09:07.243686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:10:06.526390Z | Info | Live bytes: 686.62MB Heap size: 2996.83MB +2024-07-05T15:11:06.582655Z | Info | Live bytes: 686.62MB Heap size: 2996.83MB +2024-07-05T15:12:06.622528Z | Info | Live bytes: 686.62MB Heap size: 2996.83MB +2024-07-05T15:12:33.982639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:12:36.908302Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:12:52.331145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:12:52.594650Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:12:59.484365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:00.737647Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:13:06.629952Z | Info | Live bytes: 726.69MB Heap size: 2996.83MB +2024-07-05T15:13:17.724948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:18.473087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:19.892242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:21.606440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:22.132333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:22.757512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:23.374797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:24.028291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:26.208926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:26.716774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:27.215290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:28.257920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:29.058207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:30.045483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:30.873709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:31.544084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:32.361877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:32.872237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:34.755332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:43.556677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:46.453305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:47.514751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:13:48.194589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:02.058178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:02.869327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:06.634541Z | Info | Live bytes: 813.22MB Heap size: 2996.83MB +2024-07-05T15:14:13.634001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:14.887693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:15.439355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:20.571386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:29.869710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:32.290946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:33.614750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:34.435915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:37.521803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:38.234250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:39.021673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:40.080076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:40.920301Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:14:41.593692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:49.652972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:14:50.101109Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:15:01.483307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:15:02.309375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:15:04.745398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:15:05.490996Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:15:06.637542Z | Info | Live bytes: 853.12MB Heap size: 2996.83MB +2024-07-05T15:16:06.639593Z | Info | Live bytes: 853.12MB Heap size: 2996.83MB +2024-07-05T15:16:07.610029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:10.610500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:21.868516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:25.681855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:26.587432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:27.151379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:28.907760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:29.014504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:29.187178Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:29.286863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:29.352076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:29.414988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:29.869772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:35.750196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:43.446255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:56.537333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:57.145831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:57.900740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:58.633959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:59.217904Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:59.335816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:59.434738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:59.557994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:59.661202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:59.832775Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:16:59.874082Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:16:59.890627Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:00.568155Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:00.848891Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:01.017817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:01.103597Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:01.379439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:01.559936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:02.221872Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:02.533635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:02.670036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:03.262988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:06.643874Z | Info | Live bytes: 875.29MB Heap size: 2996.83MB +2024-07-05T15:17:10.168019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:11.237630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:26.724282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:27.640965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:28.137343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:28.768117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:29.614449Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:29.743645Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:29.932315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:30.052820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:30.055124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:30.146563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:30.208481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:17:30.595795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:32.021939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:35.732515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:39.059048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:40.965446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:46.488133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:47.723771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:17:55.750133Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:17:56.294625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:18:06.647439Z | Info | Live bytes: 899.13MB Heap size: 2996.83MB +2024-07-05T15:19:06.669658Z | Info | Live bytes: 899.13MB Heap size: 2996.83MB +2024-07-05T15:19:27.525315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:41.292625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:44.113037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:44.663431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:47.258717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:48.650143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:49.516330Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:19:49.567200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:56.552149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:19:56.872829Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:20:06.678737Z | Info | Live bytes: 909.37MB Heap size: 2996.83MB +2024-07-05T15:20:28.950815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:29.633071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:30.180181Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:20:30.247247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:36.832823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:38.533885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:39.240778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:41.474876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:41.995840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:43.908283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:20:44.489089Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:21:06.691350Z | Info | Live bytes: 915.40MB Heap size: 2996.83MB +2024-07-05T15:22:06.751495Z | Info | Live bytes: 915.40MB Heap size: 2996.83MB +2024-07-05T15:23:06.812470Z | Info | Live bytes: 915.40MB Heap size: 2996.83MB +2024-07-05T15:24:04.734205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:06.669077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:06.765355Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:06.813936Z | Info | Live bytes: 922.91MB Heap size: 2996.83MB +2024-07-05T15:24:07.219873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:07.740038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:08.179522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:08.256439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:09.246494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:09.477500Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:09.670164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:09.937869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:10.503235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:11.069857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:11.621502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:12.453264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:12.971184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:13.498084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:14.006253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:14.731212Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:14.809024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:14.892544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:14.986701Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:15.070835Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:15.148336Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:15.294743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:15.440631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:15.857325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:16.300925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:16.347816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:16.446384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:16.570051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:16.808875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:17.336979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:17.861262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:18.912619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:18.999968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:19.136848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:19.227521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:19.284606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:19.586365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:19.610261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:20.184184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:20.956476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:21.871683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:22.505174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:23.108649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:24.726353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:26.100543Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:27.651571Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:27.742176Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:27.818473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:27.968880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:28.591109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:28.821309Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:28.891547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:28.931084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.006346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.102966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.391899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:29.399584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.591727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.737804Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.789290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.869536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:29.917506Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:30.053745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:30.143202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:30.608603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:31.227609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:32.040835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:34.895835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:35.499101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:36.055673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:40.708974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:41.511027Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:24:41.527435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:45.581794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:46.091980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:46.647185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:47.141349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:24:47.215857Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:24:47.753011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:25:06.834675Z | Info | Live bytes: 949.32MB Heap size: 2996.83MB +2024-07-05T15:26:06.895931Z | Info | Live bytes: 949.32MB Heap size: 2996.83MB +2024-07-05T15:27:06.956966Z | Info | Live bytes: 949.32MB Heap size: 2996.83MB +2024-07-05T15:27:52.495060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:53.504578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:53.971219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:27:54.132419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:54.825528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:55.059228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:27:55.362545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:55.922933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:56.054379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:27:56.500622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:57.115028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:27:57.115064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:57.166719Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:27:57.264305Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:27:57.619441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:58.388015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:27:59.385158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:00.138664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:01.454286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:02.069426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:03.142352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:03.647360Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:03.748291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:03.841228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:03.949424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:04.033400Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:04.218482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:04.291613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:05.267998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:06.960663Z | Info | Live bytes: 973.37MB Heap size: 2996.83MB +2024-07-05T15:28:33.079075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:33.601167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:33.875760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:33.983360Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:34.171439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:34.738459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:35.598632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:36.200840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:36.926205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:37.660473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:37.668092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:37.723546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:37.795732Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:37.868818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:28:38.170389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:39.010436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:43.922842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:46.826393Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:47.529045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:48.292264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:48.865982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:28:49.513640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:06.974801Z | Info | Live bytes: 984.72MB Heap size: 2996.83MB +2024-07-05T15:29:35.477850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:36.326590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:36.908716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:37.571722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:38.350804Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:29:38.800801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:39.765108Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:29:39.924060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:29:40.002359Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:29:40.082625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:29:40.219010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:54.695585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:29:55.011820Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:29:55.206633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:04.536528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:06.979351Z | Info | Live bytes: 1007.50MB Heap size: 2996.83MB +2024-07-05T15:30:14.401406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:43.569134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:52.619795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:54.807572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:55.335366Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:30:55.599990Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:30:55.784354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:56.324354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:56.382361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:30:56.845128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:57.342360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:58.396583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:58.447503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:30:58.911792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:30:59.514167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:00.025674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:03.429435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:06.442108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:06.980423Z | Info | Live bytes: 1032.13MB Heap size: 2996.83MB +2024-07-05T15:31:07.434891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:07.664079Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:07.904793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:08.105135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:08.543950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:08.694363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:08.808150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:09.560990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:10.133968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:14.359464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:33.001568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:33.486808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:33.567279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:33.602805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:33.682143Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:33.953265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:34.125466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:31:34.132332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:34.307928Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:31:34.751884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:32:07.007550Z | Info | Live bytes: 1070.55MB Heap size: 2996.83MB +2024-07-05T15:33:07.021857Z | Info | Live bytes: 1070.55MB Heap size: 2996.83MB +2024-07-05T15:34:07.083054Z | Info | Live bytes: 1070.55MB Heap size: 2996.83MB +2024-07-05T15:35:07.144126Z | Info | Live bytes: 1070.55MB Heap size: 2996.83MB +2024-07-05T15:36:07.186047Z | Info | Live bytes: 1070.55MB Heap size: 2996.83MB +2024-07-05T15:36:22.545114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:22.618053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:22.893613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:23.682532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:23.874288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:24.117078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:25.774501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:26.025545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:26.139222Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:26.338327Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:26.400823Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:26.460249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:26.560634Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:26.719048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:26.950363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:27.006333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:27.998110Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:28.184229Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:28.275025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:28.300565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:28.353509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:28.652661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:28.802418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:28.856282Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:29.299240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:29.759095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:30.157110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:30.839532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:40.021632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:40.549585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:41.141227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:42.172239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:42.873854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:46.615162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:50.319812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:51.152663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:51.319655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:51.519466Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:51.744553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:56.801873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:58.187756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:36:58.626544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:36:59.440962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:01.083304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:01.702918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:02.538297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:07.192164Z | Info | Live bytes: 1088.83MB Heap size: 2996.83MB +2024-07-05T15:37:09.041377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:18.842124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:19.499764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:20.134282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:20.270543Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:37:20.942741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:27.052417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:27.589215Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:37:27.628318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:28.129424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:28.641706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:30.835563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-05T15:37:30.888719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:32.958353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:33.538635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:33.808980Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:37:45.000406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:45.667015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:37:45.721759Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-05T15:38:07.213162Z | Info | Live bytes: 1115.63MB Heap size: 2996.83MB +2024-07-05T15:39:02.438364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T15:39:07.217451Z | Info | Live bytes: 1150.67MB Heap size: 2996.83MB +2024-07-05T15:40:07.273635Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:41:07.334599Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:42:07.341641Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:43:07.391579Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:44:07.437664Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:45:07.498864Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:46:07.533594Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:47:07.594614Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:48:07.655955Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:49:07.717152Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:50:07.774483Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:51:07.835737Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:52:07.853739Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:53:07.904364Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:54:07.965529Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:55:08.026427Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:56:08.061722Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:57:08.122889Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:58:08.184296Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T15:59:08.205703Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:00:08.267066Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:01:08.328313Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:02:08.389338Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:03:08.397756Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:04:08.459176Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:05:08.487422Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:06:08.518534Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:07:08.560468Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:08:08.621725Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:09:08.653762Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:10:08.714873Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:11:08.757726Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:12:08.781790Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:13:08.789767Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:14:08.851162Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:15:08.902452Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:16:08.963502Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:17:08.973697Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:18:09.021972Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:19:09.083426Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:20:09.129751Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:21:09.191130Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:22:09.197753Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:23:09.207732Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:24:09.261560Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:25:09.322608Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:26:09.325753Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:27:09.387045Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:28:09.448288Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:29:09.502508Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:30:09.563386Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:31:09.621673Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:32:09.630268Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:33:09.661984Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:34:09.723384Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:35:09.784733Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:36:09.846137Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:37:09.907564Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:38:09.968963Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:39:10.030391Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:40:10.091758Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:41:10.093736Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:42:10.154914Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:43:10.216256Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:44:10.229339Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:45:10.290496Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:46:10.350502Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:47:10.411501Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:48:10.459379Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:49:10.519553Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:50:10.580946Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:51:10.585554Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:52:10.605733Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:53:10.615446Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:54:10.669639Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:55:10.730903Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:56:10.755858Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:57:10.765802Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:58:10.826591Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T16:59:10.887694Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:00:10.891443Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:01:10.913738Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:02:10.957393Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:03:11.018422Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:04:11.043772Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:05:11.050755Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:06:11.084178Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:07:11.145434Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:08:11.206526Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:09:11.267710Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:10:11.297103Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:11:11.358485Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:12:11.419881Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:13:11.481298Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:14:11.542284Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:15:11.567596Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:16:11.627519Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:17:11.688519Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:18:11.749466Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:19:11.809452Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:20:11.829633Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:21:11.890375Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:22:11.944853Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:23:12.005664Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:24:12.056341Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:25:12.116295Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:26:12.123570Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:27:12.184774Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:28:12.241945Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:29:12.301847Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:30:12.307565Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:31:12.338573Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:32:12.399361Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:33:12.404231Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:34:12.465155Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:35:12.526409Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:36:12.587304Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:37:12.592267Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:38:12.652326Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:39:12.713045Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:40:12.774454Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:41:12.836077Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:42:12.896965Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:43:12.900226Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:44:12.948336Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:45:12.969395Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:46:13.030128Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:47:13.091334Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:48:13.151330Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:49:13.154376Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:50:13.214536Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:51:13.261601Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:52:13.322400Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:53:13.382267Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:54:13.389409Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:55:13.449366Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:56:13.502697Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:57:13.563887Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:58:13.624326Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T17:59:13.684973Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:00:13.746392Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:01:13.807414Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:02:13.867933Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:03:13.927395Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:04:13.981863Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:05:14.043331Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:06:14.104450Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:07:14.164897Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:08:14.225788Z | Info | Live bytes: 1157.07MB Heap size: 2996.83MB +2024-07-05T18:08:27.072900Z | Info | LSP: received shutdown +2024-07-05T18:08:27.074988Z | Error | Got EOF +2024-07-05 18:23:08.3400000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-05 18:23:08.3410000 [client] INFO Finding haskell-language-server +2024-07-05 18:23:08.3420000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:08.3420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:08.3480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-05 18:23:08.4860000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:08.4870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:08.4920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-05 18:23:08.6190000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:08.6200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:08.6260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-05 18:23:08.7680000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:08.7680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:08.7740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-05 18:23:08.9680000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:08.9690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:08.9750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-05 18:23:08.9920000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:08.9920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:08.9990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-05 18:23:09.0140000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:09.0140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:09.0200000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-05 18:23:09.0470000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-05 18:23:09.1010000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:09.1010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:09.1060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-05 18:23:09.2230000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-05 18:23:09.2240000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-05 18:23:21.3870000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-05 18:23:21.4470000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-05 18:23:21.4470000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:21.4470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:21.4530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-05 18:23:21.5490000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:21.5490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:21.5540000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-05 18:23:21.5700000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:21.5700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:21.5750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.0' in cwd '/home/jordan' +2024-07-05 18:23:21.5880000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:21.5880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:21.5940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-05 18:23:21.6100000 [client] INFO Checking for ghcup installation +2024-07-05 18:23:21.6100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-05 18:23:21.6160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.0 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-05 18:23:21.7130000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-05 18:23:21.7140000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-05 18:23:21.7140000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-05 18:23:21.7140000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-05 18:23:21.7140000 [client] INFO server environment variables: +2024-07-05 18:23:21.7140000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-05 18:23:21.7140000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-05 18:23:21.7140000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.0_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-05 18:23:21.7160000 [client] INFO Starting language server +2024-07-05T18:23:33.105773Z | Info | haskell-language-server version: 2.9.0.0 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.0/lib/haskell-language-server-2.9.0.0/bin/haskell-language-server-9.6.5) +2024-07-05T18:23:33.106647Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-05T18:23:33.106904Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-05T18:23:33.109522Z | Info | Logging heap statistics every 60.00s +2024-07-05T18:23:33.118693Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-05T18:23:33.119173Z | Info | Starting server +2024-07-05T18:23:33.120612Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-05T18:23:33.161198Z | Info | Started LSP server in 0.04s +2024-07-05T18:23:34.612924Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query.hs +2024-07-05T18:23:34.613886Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T18:23:35.157609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:23:35.157657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:23:36.577492Z | Info | Load cabal cradle using single file +2024-07-05T18:23:37.809356Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT810964-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T18:23:46.773001Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-1615d6206a80f4a0e31ef63d6e69b655fd28231c +2024-07-05T18:23:46.784709Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-05T18:24:27.524288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:24:33.112055Z | Info | Live bytes: 406.62MB Heap size: 1659.90MB +2024-07-05T18:25:33.173345Z | Info | Live bytes: 406.62MB Heap size: 1659.90MB +2024-07-05T18:26:33.183612Z | Info | Live bytes: 406.62MB Heap size: 1659.90MB +2024-07-05T18:27:33.244423Z | Info | Live bytes: 406.62MB Heap size: 1659.90MB +2024-07-05T18:27:40.802752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:28:30.190612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:28:33.247583Z | Info | Live bytes: 478.45MB Heap size: 2038.43MB +2024-07-05T18:28:51.194004Z | Info | Cradle path: cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/Address.hs +2024-07-05T18:28:51.194719Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-05T18:28:51.228576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:28:52.736679Z | Info | Load cabal cradle using single file +2024-07-05T18:28:53.664755Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:test:cardano-api-test + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT810964-8 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-05T18:28:54.090123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:29:17.458573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:29:22.107300Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/main-dc43488629f1d14bba6bb01a2a59684a12b6e207-dc43488629f1d14bba6bb01a2a59684a12b6e207 +2024-07-05T18:29:22.107751Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-dc43488629f1d14bba6bb01a2a59684a12b6e207 +2024-07-05T18:29:22.112229Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-8.49.0.0-inplace-internal + , main-dc43488629f1d14bba6bb01a2a59684a12b6e207 ] +2024-07-05T18:29:33.249332Z | Info | Live bytes: 1047.94MB Heap size: 2663.38MB +2024-07-05T18:29:52.631964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:30:33.251726Z | Info | Live bytes: 1063.37MB Heap size: 2663.38MB +2024-07-05T18:31:33.313020Z | Info | Live bytes: 1063.37MB Heap size: 2663.38MB +2024-07-05T18:32:29.713215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:32:33.314811Z | Info | Live bytes: 1086.30MB Heap size: 2663.38MB +2024-07-05T18:33:33.375369Z | Info | Live bytes: 1086.30MB Heap size: 2663.38MB +2024-07-05T18:34:12.777293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:34:19.100739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:34:33.376883Z | Info | Live bytes: 1086.30MB Heap size: 2663.38MB +2024-07-05T18:34:33.745754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T18:35:33.430856Z | Info | Live bytes: 1083.24MB Heap size: 2663.38MB +2024-07-05T18:36:33.451051Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:37:33.511526Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:38:33.572385Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:39:33.633424Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:40:33.639710Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:41:33.700432Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:42:33.761163Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:43:33.773175Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:44:33.833512Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:45:33.875655Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:46:33.936367Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:47:33.996911Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:48:34.029788Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:49:34.061645Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:50:34.093783Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:51:34.125715Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:52:34.187066Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:53:34.189762Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:54:34.197726Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:55:34.259116Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:56:34.320427Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:57:34.381933Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:58:34.405590Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T18:59:34.467017Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:00:34.528997Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:01:34.581697Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:02:34.643461Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:03:34.704886Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:04:34.766166Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:05:34.813326Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:06:34.815992Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:07:34.877634Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:08:34.939441Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:09:34.957586Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:10:34.989722Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:11:35.051406Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:12:35.113149Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:13:35.174521Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:14:35.236066Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:15:35.297878Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:16:35.359441Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:17:35.420705Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:18:35.481957Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:19:35.543510Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:20:35.604944Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:21:35.666372Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:22:35.727770Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:23:35.789391Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:24:35.850927Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:25:35.912510Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:26:35.973979Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:27:36.035532Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:28:36.096992Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:29:36.158306Z | Info | Live bytes: 1106.98MB Heap size: 2663.38MB +2024-07-05T19:30:33.406018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T19:30:36.160178Z | Info | Live bytes: 1096.14MB Heap size: 2663.38MB +2024-07-05T19:31:36.215598Z | Info | Live bytes: 1096.14MB Heap size: 2663.38MB +2024-07-05T19:32:36.276826Z | Info | Live bytes: 1096.14MB Heap size: 2663.38MB +2024-07-05T19:33:36.301749Z | Info | Live bytes: 1096.14MB Heap size: 2663.38MB +2024-07-05T19:34:36.362540Z | Info | Live bytes: 1096.14MB Heap size: 2663.38MB +2024-07-05T19:35:36.423835Z | Info | Live bytes: 1096.14MB Heap size: 2663.38MB +2024-07-05T19:35:50.405637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T19:36:06.261215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T19:36:36.438980Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:37:36.500435Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:38:36.561917Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:39:36.623417Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:40:36.645399Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:41:36.706358Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:42:36.767583Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:43:36.828713Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:44:36.889660Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:45:36.903527Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:46:36.964738Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:47:37.026309Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:48:37.087726Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:49:37.133741Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:50:37.195335Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:51:37.197745Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:52:37.259289Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:53:37.261648Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:54:37.322836Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:55:37.325700Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:56:37.387093Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:57:37.448650Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:58:37.503701Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T19:59:37.508349Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:00:37.569787Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:01:37.630385Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:02:37.677765Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:03:37.739297Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:04:37.800644Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:05:37.861908Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:06:37.923320Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:07:37.984704Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:08:38.046109Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:09:38.107419Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:10:38.169116Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:11:38.192626Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:12:38.253605Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:13:38.264740Z | Info | Live bytes: 1297.59MB Heap size: 2663.38MB +2024-07-05T20:14:13.691819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:14:14.484354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:14:38.269742Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:15:38.285552Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:16:38.294436Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:17:38.355354Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:18:38.414169Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:19:38.445373Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:20:38.506123Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:21:38.567266Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:22:38.628355Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:23:38.689338Z | Info | Live bytes: 1411.39MB Heap size: 2663.38MB +2024-07-05T20:24:38.701768Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:25:38.763571Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:26:38.824636Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:27:38.841693Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:28:38.902632Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:29:38.939118Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:30:39.000096Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:31:39.005722Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:32:39.007977Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:33:39.069447Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:34:39.130705Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:35:39.191344Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:36:39.197321Z | Info | Live bytes: 1428.49MB Heap size: 2663.38MB +2024-07-05T20:37:39.208447Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:38:39.269213Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:39:39.303845Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:40:39.320293Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:41:39.364185Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:42:39.424811Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:43:39.437659Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:44:39.443989Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:45:39.501766Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:46:39.540278Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:47:14.498405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:47:39.564834Z | Info | Live bytes: 1445.75MB Heap size: 2663.38MB +2024-07-05T20:48:05.671070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:15.144727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:15.849036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:16.457014Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:16.991616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:17.586580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:18.381121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:18.949650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:24.781996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:38.896261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:39.566959Z | Info | Live bytes: 1491.29MB Heap size: 2720.01MB +2024-07-05T20:48:39.602167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:40.120417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:40.859193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T20:48:41.462900Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Value.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ValueParser.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-07-05T20:49:39.614271Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:50:39.661632Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:51:39.722341Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:52:39.780550Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:53:39.786514Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:54:39.789077Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:55:39.850308Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:56:39.894009Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:57:39.905318Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:58:39.965359Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T20:59:40.025938Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T21:00:40.086729Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T21:01:40.141728Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T21:02:40.203162Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T21:03:40.236910Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T21:04:34.914581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:04:40.241528Z | Info | Live bytes: 1542.35MB Heap size: 2761.95MB +2024-07-05T21:05:10.864160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:05:13.419306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:05:15.113435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:05:40.260061Z | Info | Live bytes: 1619.26MB Heap size: 2812.28MB +2024-07-05T21:06:40.320387Z | Info | Live bytes: 1619.26MB Heap size: 2812.28MB +2024-07-05T21:07:40.349527Z | Info | Live bytes: 1619.26MB Heap size: 2812.28MB +2024-07-05T21:08:02.424654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:08:09.585686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:08:40.382133Z | Info | Live bytes: 1636.52MB Heap size: 2846.88MB +2024-07-05T21:09:40.442341Z | Info | Live bytes: 1636.52MB Heap size: 2846.88MB +2024-07-05T21:09:47.598596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:10:40.494718Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:11:40.536493Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:12:40.597611Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:13:40.602543Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:14:25.439726Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-05T21:14:40.617542Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:15:40.645997Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:16:40.685628Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:17:40.696378Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:18:40.758347Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:19:40.819567Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:20:40.831926Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:21:40.837694Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:22:40.858590Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:23:40.872447Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:24:40.933541Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:25:40.994374Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:26:41.055617Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:27:41.112408Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:28:41.142748Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:29:41.175306Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:30:41.236617Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:31:41.298049Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:32:41.359700Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:33:41.421013Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:34:41.429774Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:35:41.441649Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:36:41.502708Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:37:41.564243Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:38:41.625680Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:39:41.687128Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:40:41.748596Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:41:41.789593Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:42:41.793815Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:43:41.837122Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:44:41.898677Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:45:41.933729Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:46:41.969132Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:47:42.016114Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:48:42.065146Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:49:42.126573Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:50:42.165736Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:51:42.219436Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:52:42.232351Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:53:42.293212Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:54:42.345484Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:55:42.373635Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:56:42.389108Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:57:42.404434Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:58:42.465789Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T21:59:42.527169Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T22:00:42.588403Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T22:01:42.649389Z | Info | Live bytes: 1650.35MB Heap size: 2869.95MB +2024-07-05T22:01:53.223916Z | Error | Got EOF +2024-07-07 19:11:47.5200000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-07 19:11:47.5230000 [client] INFO Finding haskell-language-server +2024-07-07 19:11:47.5250000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:47.5260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:47.5410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-07 19:11:51.1900000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:51.1900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:51.1970000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-07 19:11:51.4460000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:51.4470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:51.4560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-07 19:11:51.6730000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:51.6730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:51.6800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-07 19:11:51.8350000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:51.8350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:51.8410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-07 19:11:51.8570000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:51.8570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:51.8630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-07 19:11:51.8810000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:51.8810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:51.8890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-07 19:11:51.9090000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-07 19:11:52.0760000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:52.0770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:52.0850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-07 19:11:52.3400000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-07 19:11:52.3460000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-07 19:11:56.9220000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-07 19:11:56.9870000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-07 19:11:56.9870000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:56.9870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:56.9940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-07 19:11:57.1100000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:57.1100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:57.1160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-07 19:11:57.1370000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:57.1370000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:57.1420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-07 19:11:57.1580000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:57.1580000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:57.1650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-07 19:11:57.1820000 [client] INFO Checking for ghcup installation +2024-07-07 19:11:57.1820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-07 19:11:57.1880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-07 19:11:57.3750000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-07 19:11:57.3760000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-07 19:11:57.3760000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-07 19:11:57.3760000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-07 19:11:57.3760000 [client] INFO server environment variables: +2024-07-07 19:11:57.3760000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-07 19:11:57.3760000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-07 19:11:57.3760000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-07 19:11:57.3780000 [client] INFO Starting language server +2024-07-07T19:12:08.909916Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-07T19:12:08.912025Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-07T19:12:08.912323Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-07T19:12:08.915802Z | Info | Logging heap statistics every 60.00s +2024-07-07T19:12:08.924261Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-07T19:12:08.924908Z | Info | Starting server +2024-07-07T19:12:08.939858Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-07T19:12:09.016236Z | Info | Started LSP server in 0.09s +2024-07-07T19:12:10.500977Z | Info | Cradle path: cardano-api/internal/Cardano/Api/SerialiseRaw.hs +2024-07-07T19:12:10.502160Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-07T19:12:11.068561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-07T19:12:12.075884Z | Info | Load cabal cradle using single file +2024-07-07T19:12:13.084963Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT25182-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-07T19:12:16.990936Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-1615d6206a80f4a0e31ef63d6e69b655fd28231c +2024-07-07T19:12:16.998387Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-07T19:13:08.968009Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:14:09.028646Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:15:09.089132Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:16:09.149816Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:17:09.210579Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:18:09.271451Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:19:09.332319Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:20:09.392550Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:21:09.401694Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:22:09.461595Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:23:09.522164Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:24:09.583066Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:25:09.644091Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:26:09.665460Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:27:09.725368Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:28:09.785558Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:29:09.845624Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:30:09.905584Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:31:09.965540Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:32:09.979453Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:33:10.039547Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:34:10.100357Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:35:10.160983Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:36:10.178429Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:37:10.238467Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:38:10.298498Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:39:10.359202Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:40:10.420042Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:41:10.459994Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:42:10.520761Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:43:10.581609Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:44:10.596631Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:45:10.657624Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:46:10.718628Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:47:10.779362Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:48:10.829608Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:49:10.857588Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:50:10.885850Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:51:10.946972Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:52:10.970224Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:53:11.031246Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:54:11.091586Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:55:11.101097Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:56:11.162496Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:57:11.223372Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:58:11.284407Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T19:59:11.291648Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:00:11.343541Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:01:11.356497Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:02:11.416687Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:03:11.453960Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:04:11.515622Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:05:11.576783Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:06:11.626398Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:07:11.686501Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:08:11.747366Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:09:11.807945Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:10:11.869626Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:11:11.879494Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:12:11.940633Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:13:11.951441Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:14:11.999927Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:15:12.022140Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:16:12.071394Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:17:12.101155Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:18:12.161596Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:19:12.222732Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:20:12.283967Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:21:12.343472Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:22:12.404083Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:23:12.421699Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:24:12.482688Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:25:12.543463Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:26:12.583987Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:27:12.645797Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:28:12.692923Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:29:12.752379Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:30:12.754066Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:31:12.815374Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:32:12.845381Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:33:12.906252Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:34:12.918658Z | Info | Live bytes: 292.20MB Heap size: 1654.65MB +2024-07-07T20:34:58.769090Z | Info | LSP: received shutdown +2024-07-07T20:34:58.770925Z | Info | Reactor thread stopped +2024-07-07T20:34:58.771532Z | Error | Got EOF +2024-07-08 07:43:53.7700000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-08 07:43:53.7710000 [client] INFO Finding haskell-language-server +2024-07-08 07:43:53.7720000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:53.7720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:53.7770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-08 07:43:53.8730000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:53.8730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:53.8770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-08 07:43:54.0290000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:54.0290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:54.0320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-08 07:43:54.1710000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:54.1710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:54.1770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-08 07:43:54.2970000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:54.2970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:54.3010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-08 07:43:54.3200000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:54.3200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:54.3250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-08 07:43:54.3500000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:54.3510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:54.3570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-08 07:43:54.3780000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-08 07:43:54.4240000 [client] INFO Checking for ghcup installation +2024-07-08 07:43:54.4250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:43:54.4300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-08 07:43:54.5450000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-08 07:43:54.5450000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-08 07:44:00.9070000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-08 07:44:00.9650000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-08 07:44:00.9660000 [client] INFO Checking for ghcup installation +2024-07-08 07:44:00.9660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:44:00.9740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-08 07:44:01.0600000 [client] INFO Checking for ghcup installation +2024-07-08 07:44:01.0600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:44:01.0630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-08 07:44:01.0780000 [client] INFO Checking for ghcup installation +2024-07-08 07:44:01.0780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:44:01.0810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-08 07:44:01.0950000 [client] INFO Checking for ghcup installation +2024-07-08 07:44:01.0950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:44:01.0990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-08 07:44:01.1140000 [client] INFO Checking for ghcup installation +2024-07-08 07:44:01.1150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-08 07:44:01.1220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-08 07:44:01.2070000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-08 07:44:01.2080000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-08 07:44:01.2080000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-08 07:44:01.2080000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-08 07:44:01.2080000 [client] INFO server environment variables: +2024-07-08 07:44:01.2080000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-08 07:44:01.2080000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-08 07:44:01.2080000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-08 07:44:01.2090000 [client] INFO Starting language server +2024-07-08T07:44:10.610430Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-08T07:44:10.611831Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-08T07:44:10.612049Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-08T07:44:10.614473Z | Info | Logging heap statistics every 60.00s +2024-07-08T07:44:10.621172Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-08T07:44:10.621585Z | Info | Starting server +2024-07-08T07:44:10.635149Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-08T07:44:10.698139Z | Info | Started LSP server in 0.08s +2024-07-08T07:44:12.098176Z | Info | Cradle path: cardano-api/internal/Cardano/Api/SerialiseRaw.hs +2024-07-08T07:44:12.098894Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-08T07:44:12.669927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T07:44:13.429379Z | Info | Load cabal cradle using single file +2024-07-08T07:44:14.274268Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT23506-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-08T07:44:17.648918Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-1615d6206a80f4a0e31ef63d6e69b655fd28231c +2024-07-08T07:44:17.653574Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-08T07:45:10.668457Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:46:10.678269Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:47:10.705573Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:48:10.766487Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:49:10.780284Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:50:10.840488Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:51:10.898824Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:52:10.960178Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:53:11.020507Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:54:11.081524Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:55:11.142181Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:56:11.202623Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:57:11.263382Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:58:11.305838Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T07:59:11.367051Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T08:00:11.428197Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T08:01:11.446193Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T08:02:11.447034Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T08:03:11.508663Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T08:04:11.568922Z | Info | Live bytes: 83.37MB Heap size: 1245.71MB +2024-07-08T08:04:38.650698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:04:43.180387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:05:11.584469Z | Info | Live bytes: 377.61MB Heap size: 1779.43MB +2024-07-08T08:05:13.972774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:05:25.644217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:06:11.617546Z | Info | Live bytes: 425.00MB Heap size: 1779.43MB +2024-07-08T08:07:11.649495Z | Info | Live bytes: 425.00MB Heap size: 1779.43MB +2024-07-08T08:08:11.710684Z | Info | Live bytes: 431.92MB Heap size: 1779.43MB +2024-07-08T08:09:11.713644Z | Info | Live bytes: 431.92MB Heap size: 1779.43MB +2024-07-08T08:09:13.458570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:10:11.772323Z | Info | Live bytes: 431.92MB Heap size: 1779.43MB +2024-07-08T08:11:11.777566Z | Info | Live bytes: 431.92MB Heap size: 1779.43MB +2024-07-08T08:12:11.807879Z | Info | Live bytes: 431.92MB Heap size: 1779.43MB +2024-07-08T08:12:21.451735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:12:49.476343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:13:11.828822Z | Info | Live bytes: 432.88MB Heap size: 1779.43MB +2024-07-08T08:14:11.873234Z | Info | Live bytes: 432.88MB Heap size: 1779.43MB +2024-07-08T08:15:11.934240Z | Info | Live bytes: 432.88MB Heap size: 1779.43MB +2024-07-08T08:16:11.937890Z | Info | Live bytes: 432.88MB Heap size: 1779.43MB +2024-07-08T08:17:11.999729Z | Info | Live bytes: 432.88MB Heap size: 1779.43MB +2024-07-08T08:17:31.954949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:17:46.682830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:17:47.890461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:17:48.560397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:17:49.165552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:08.565522Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:09.550839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:11.446188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:12.001493Z | Info | Live bytes: 565.71MB Heap size: 1849.69MB +2024-07-08T08:18:12.027059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:12.640664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:13.277991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:13.888294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:14.546538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:15.166669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:15.937126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:16.574280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:17.139084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:17.748675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:18.365186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:18.957548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:19.607655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:20.231268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:20.870347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:21.860132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:22.443619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:23.221213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:23.857521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:24.503017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:25.136871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:26.163125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:26.884550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:27.642479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:28.334478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:29.970324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:30.546076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:31.233519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:31.898826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:32.478150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:33.189588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:33.768165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:18:34.370195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:11.588131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:12.002384Z | Info | Live bytes: 617.25MB Heap size: 2239.76MB +2024-07-08T08:19:12.149783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:12.782576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:18.990596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:20.384385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:21.065989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:22.542605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:23.211723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:23.873636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:25.431848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:27.655139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:28.272016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:29.653586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:30.272988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:30.903260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:32.077214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:33.206159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:34.041862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:35.343035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:36.095770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:39.217998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:40.519974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:41.921931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:42.495283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:43.106742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:44.193787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:44.816551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:45.505663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:47.825491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:48.793442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:53.433087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:54.043030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:54.885894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:55.492457Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:56.299143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:56.935838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:57.583258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:58.274125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:19:59.219625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:00.175464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:00.844754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:01.452142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:02.180119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:02.778133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:03.719149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:04.344881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:04.987337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:05.635115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:06.061894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T08:20:06.210579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:06.788688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:07.518913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:08.370989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:09.045097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:20:12.006420Z | Info | Live bytes: 513.57MB Heap size: 2471.49MB +2024-07-08T08:20:15.127453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:21:12.064786Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:22:12.126558Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:23:12.188168Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:24:12.213419Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:25:12.217508Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:26:12.278940Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:27:12.340681Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:28:12.401857Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:29:12.417393Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:30:12.465436Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:31:12.526414Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:32:12.587194Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:33:12.647870Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:34:12.689344Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:35:12.750339Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:36:12.811765Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:37:12.873100Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:38:12.933260Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:39:12.940345Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:40:12.953967Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:40:26.047243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:41:13.001239Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:42:13.043969Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:43:13.102582Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:44:13.163384Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:45:13.171204Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:46:13.232088Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:47:13.251559Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:47:56.053956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T08:48:13.263352Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:49:13.324507Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:50:13.345651Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:51:13.406343Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:52:13.466590Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:53:13.521904Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:54:13.540859Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:55:13.571630Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:56:13.602870Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:57:13.656931Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:58:13.681802Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T08:59:13.708551Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:00:13.743404Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:01:13.804201Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:02:13.865300Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:03:13.922441Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:04:13.969728Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:05:14.017624Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:06:14.078931Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:07:14.140266Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:08:14.195609Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:09:14.256880Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:10:14.305575Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:11:14.366873Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:12:14.425086Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:13:14.463846Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:14:14.524292Z | Info | Live bytes: 516.10MB Heap size: 2471.49MB +2024-07-08T09:14:17.049746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:15:07.488020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:15:14.526260Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:15:38.372667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:16:14.563382Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:17:14.624440Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:18:14.679992Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:19:14.722519Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:20:14.768379Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:21:14.829386Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:22:14.890287Z | Info | Live bytes: 739.03MB Heap size: 2471.49MB +2024-07-08T09:22:35.185012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:04.126230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:14.929235Z | Info | Live bytes: 749.61MB Heap size: 2471.49MB +2024-07-08T09:23:27.641822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:28.291080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:34.812175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:36.874286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:39.951584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:40.506918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:40.620189Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:40.709457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:40.862811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:41.235198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:41.737201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:42.087062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:42.287367Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:42.322052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:42.455933Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:42.561843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:42.649728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:42.805851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:42.953489Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:23:42.978497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:23:43.593771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:24:14.960668Z | Info | Live bytes: 769.31MB Heap size: 2471.49MB +2024-07-08T09:25:15.021900Z | Info | Live bytes: 769.31MB Heap size: 2471.49MB +2024-07-08T09:25:20.049016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:25:46.481602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:25:51.226838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:25:51.722637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:25:51.791427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:25:59.374352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:00.048146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:00.094265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:00.191267Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:00.294420Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:00.625491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:00.688858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:00.821095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:01.206311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:01.842292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:02.747027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:03.330993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:03.507856Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:03.700237Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:03.755803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:03.850114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:03.978924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:04.140107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:04.358229Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:04.511460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:04.597761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:04.668679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:04.685774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:04.770875Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:05.033895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:05.177903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:05.265739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:05.306915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:05.362009Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:05.462121Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:05.654839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:05.898202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:06.314608Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:26:06.851316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:26:15.031987Z | Info | Live bytes: 818.79MB Heap size: 2471.49MB +2024-07-08T09:27:15.041606Z | Info | Live bytes: 818.79MB Heap size: 2471.49MB +2024-07-08T09:27:57.479712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:28:15.045974Z | Info | Live bytes: 828.78MB Heap size: 2471.49MB +2024-07-08T09:29:15.106363Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:30:15.114387Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:31:15.175323Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:32:15.235227Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:33:15.295898Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:34:15.306849Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:35:15.367830Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:36:15.429154Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:37:15.473695Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:38:15.535215Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:39:15.574806Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:40:15.585510Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:41:15.646647Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:42:15.707490Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:43:15.768448Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:44:15.796600Z | Info | Live bytes: 829.37MB Heap size: 2471.49MB +2024-07-08T09:44:54.890261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:09.491509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:10.156022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:10.759239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:10.823803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:11.359011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:12.191956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:12.235756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:12.770269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:13.645590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:14.933784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:15.670044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:15.798465Z | Info | Live bytes: 847.51MB Heap size: 2471.49MB +2024-07-08T09:45:16.655523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:17.886654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:18.552721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:19.097961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:19.303699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:20.246181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:20.461076Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:20.837326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:21.497525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:22.190166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:22.833751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:23.430259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:24.002299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:27.974022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:28.673294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:29.240869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:29.461770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:29.751140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:30.321377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:30.747571Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:30.908295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:31.605676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:32.233749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:32.822495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:33.833416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:34.776939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:36.271672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:36.529006Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:36.788577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:37.380895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:37.723953Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:45:38.001276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:38.739262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:39.429162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:40.196614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:45:40.975970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:46:15.834031Z | Info | Live bytes: 925.15MB Heap size: 2504.00MB +2024-07-08T09:47:15.889474Z | Info | Live bytes: 925.15MB Heap size: 2504.00MB +2024-07-08T09:48:15.898217Z | Info | Live bytes: 925.15MB Heap size: 2504.00MB +2024-07-08T09:49:15.916332Z | Info | Live bytes: 925.15MB Heap size: 2504.00MB +2024-07-08T09:49:31.449455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:31.474984Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:31.654874Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:31.772214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:32.172501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:34.211398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:34.482548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:34.782290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:40.329303Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:40.465072Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:40.577709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:40.595771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:40.664113Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.014888Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.052176Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.190005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:41.260098Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.332439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.353077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.575982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.790191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:41.828160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:41.932666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:42.019225Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:42.252017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:42.376452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:42.612313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:42.814396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:42.979758Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:43.141050Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:49:43.161381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:49:43.807853Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T09:49:44.508068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:50:15.944797Z | Info | Live bytes: 661.64MB Heap size: 2602.57MB +2024-07-08T09:51:16.005556Z | Info | Live bytes: 661.64MB Heap size: 2602.57MB +2024-07-08T09:52:16.008500Z | Info | Live bytes: 661.64MB Heap size: 2602.57MB +2024-07-08T09:52:47.642617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:52:49.918314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:49.936085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:52:50.021065Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:50.114910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:50.550787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:52:52.526205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:52:52.590654Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:52.875461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:53.053665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:53.111525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:52:53.392667Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:53.829435Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:53.911133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:52:55.949000Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:56.010277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:52:56.305178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:00.818192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:00.834667Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:01.432744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:04.957160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:05.330387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:05.454931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:05.669421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:06.013888Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:06.040337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:06.135527Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:06.327764Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:06.469933Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:06.634986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:07.314350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:07.956724Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:53:08.287536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:53:16.011697Z | Info | Live bytes: 708.32MB Heap size: 2602.57MB +2024-07-08T09:53:46.742152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:54:00.682703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:54:06.174568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:54:07.510335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:54:08.244317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:54:16.013624Z | Info | Live bytes: 716.28MB Heap size: 2602.57MB +2024-07-08T09:55:06.504514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:06.653435Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:06.829678Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:06.988369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:07.017752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:07.068648Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:07.160501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:07.603449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:07.662890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:07.750813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:07.813639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:07.900898Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:08.099459Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:08.187867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:08.237286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:08.347896Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:08.634050Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:08.767158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:08.919427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:09.284475Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:09.458773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:10.100812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:11.837286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:14.401524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:15.030586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:15.818257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:16.015655Z | Info | Live bytes: 726.13MB Heap size: 2602.57MB +2024-07-08T09:55:16.408643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:17.071026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:17.189022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:17.245930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:17.360765Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:17.608254Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:17.804112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:17.874966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:17.908441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:18.005616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:18.094417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:18.177218Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:18.390589Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:18.441879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:19.119729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:19.744098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:20.489683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:20.747433Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:55:21.060313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:21.787427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:23.753348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:30.338758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:31.000588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:40.079925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:43.176555Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:47.075200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:56.196145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:57.544794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:58.163960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:55:58.746124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:56:00.497218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:56:02.290973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:56:03.261524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:56:05.911463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:56:06.633113Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T09:56:06.729570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:56:15.205519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:56:15.771256Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T09:56:16.017067Z | Info | Live bytes: 774.45MB Heap size: 2602.57MB +2024-07-08T09:57:00.866550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:03.885716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:16.018195Z | Info | Live bytes: 777.10MB Heap size: 2602.57MB +2024-07-08T09:57:16.416465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:30.985366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:39.427808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:40.870818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:43.633708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:44.210281Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T09:57:44.436361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:45.824587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:46.360396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:46.419399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:46.445868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:46.512915Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:46.619713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:46.700801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:46.773024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:47.053344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:47.468699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:47.619288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T09:57:47.626158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:48.257496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:48.934461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:50.087699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:51.466631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:57:53.004147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T09:58:16.037610Z | Info | Live bytes: 856.78MB Heap size: 2602.57MB +2024-07-08T09:59:16.067032Z | Info | Live bytes: 856.78MB Heap size: 2602.57MB +2024-07-08T09:59:22.069335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:00:16.124334Z | Info | Live bytes: 888.14MB Heap size: 2602.57MB +2024-07-08T10:01:16.184995Z | Info | Live bytes: 888.14MB Heap size: 2602.57MB +2024-07-08T10:02:16.246042Z | Info | Live bytes: 888.14MB Heap size: 2602.57MB +2024-07-08T10:03:16.298989Z | Info | Live bytes: 888.14MB Heap size: 2602.57MB +2024-07-08T10:04:16.359319Z | Info | Live bytes: 888.14MB Heap size: 2602.57MB +2024-07-08T10:05:16.361509Z | Info | Live bytes: 888.14MB Heap size: 2602.57MB +2024-07-08T10:06:00.010972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:04.910856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:05.496632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:06.233792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:06.816286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:07.390461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:08.007308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:08.604798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:09.214149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:10.107930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:11.703482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:16.367664Z | Info | Live bytes: 893.62MB Heap size: 2602.57MB +2024-07-08T10:06:19.143920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:19.929005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:20.005157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:20.067728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:20.185707Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:20.250394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:20.455795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:21.089945Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T10:06:21.169463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:27.116832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:28.610563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:36.290316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:42.392667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:42.963539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:45.584402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:52.021957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:53.800339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:53.903651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:53.985096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:54.043072Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:54.148514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:54.230795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:54.343384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:06:54.430803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:06:55.616626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:07:01.573234Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T10:07:02.188354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:07:16.383471Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:08:16.444334Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:09:16.449588Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:10:16.481396Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:11:16.542012Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:12:16.603225Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:13:16.664181Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:14:16.673646Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:15:16.735312Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:16:16.796986Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:17:16.858742Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:18:16.920767Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:19:16.982330Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:20:17.043846Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:21:17.105196Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:22:17.166345Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:23:17.222290Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:24:17.262596Z | Info | Live bytes: 1123.79MB Heap size: 2602.57MB +2024-07-08T10:24:33.446711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:24:36.091927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:24:37.190575Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:24:45.777281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:24:46.918130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:25:17.293565Z | Info | Live bytes: 604.99MB Heap size: 2786.07MB +2024-07-08T10:25:25.293586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:26:17.313645Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:27:17.363358Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:28:17.423465Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:29:17.484257Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:30:17.544216Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:31:17.604174Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:32:17.664209Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:33:17.724539Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:34:17.785262Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:35:17.845985Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:36:17.906417Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:37:17.966212Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:38:18.026259Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:39:18.086326Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:40:18.099233Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:41:18.159216Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:42:18.189183Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:43:18.249405Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:44:18.309320Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:45:18.369373Z | Info | Live bytes: 674.57MB Heap size: 2786.07MB +2024-07-08T10:46:12.018515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:46:18.373444Z | Info | Live bytes: 686.18MB Heap size: 2786.07MB +2024-07-08T10:46:32.980310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:18.407938Z | Info | Live bytes: 707.96MB Heap size: 2786.07MB +2024-07-08T10:47:22.297324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:23.760286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:23.956205Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:24.132821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:24.263280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:24.424116Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:24.540340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:24.866064Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:24.952993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:25.069566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:25.301485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:25.426734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:47:25.599645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:26.445181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:27.068864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:28.210231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:28.840583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:29.406428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:30.765051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:31.353873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:32.303694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:32.913554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:33.585599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:34.272451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:47:36.469736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:18.446091Z | Info | Live bytes: 736.28MB Heap size: 2786.07MB +2024-07-08T10:48:25.690433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:25.963638Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:26.259052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:26.443073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:26.475277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:26.600055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:26.805207Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:26.959701Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:27.119135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:27.330421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:27.489474Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:27.860943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:28.462472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:29.137903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:29.789872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:30.577877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:31.233516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:31.993362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:32.587090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:33.373514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:50.463287Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:50.522872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:50.647416Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:50.750598Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:50.833073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:50.960009Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:51.002784Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:51.168067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:51.716490Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:52.245164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:52.787171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:53.219219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:48:53.310856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:53.914595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:54.490707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:55.139770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:55.788092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:56.487635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:57.332430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:57.935369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:58.552696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:59.176139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:48:59.749964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:01.201133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:01.390774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:01.403759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:01.497650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:01.592628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:01.666248Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:02.027728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:02.185641Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:02.315858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:02.464609Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:02.713161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:02.966135Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:03.113423Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:03.160398Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:03.255697Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:03.376750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:03.440622Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:03.492122Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:03.743764Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T10:49:04.276480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:04.978927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:05.666817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:06.265374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:06.867273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:07.470427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:08.038956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:08.639427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:09.330953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:09.923383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:10.673206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:15.412883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:18.449315Z | Info | Live bytes: 834.91MB Heap size: 2786.07MB +2024-07-08T10:49:33.158722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:35.389787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:36.059637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:37.708937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:40.591291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:41.591778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:49.307201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:50.004494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:51.042312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:51.664874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:54.327074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:55.008500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:57.350455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:58.017441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:49:58.064502Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T10:49:58.805504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T10:50:18.470366Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:51:18.531536Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:52:18.592854Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:53:18.622499Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:54:18.623945Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:55:18.685076Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:56:18.746059Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:57:18.801702Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:58:18.863187Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T10:59:18.924606Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:00:18.985958Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:01:19.047073Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:02:19.108452Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:03:19.169851Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:04:19.231366Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:05:19.292779Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:06:19.354162Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:07:19.415466Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:08:19.476933Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:09:19.538355Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:10:19.570949Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:11:19.632447Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:12:19.693820Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:13:19.755378Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:14:19.816819Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:15:19.878191Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:16:19.929003Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:17:19.990468Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:18:20.051856Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:19:20.113281Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:20:20.174639Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:21:20.221511Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:22:20.257386Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:23:20.318086Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:51:16.615665Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:52:16.639655Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:53:16.700639Z | Info | Live bytes: 866.92MB Heap size: 2786.07MB +2024-07-08T11:53:26.520346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:53:27.119202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:27.362346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:27.474111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:27.514352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:53:27.562297Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:27.658077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:27.936618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:28.119554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:28.171181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:53:28.297524Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:28.372444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:28.415593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:28.507965Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:53:28.799670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:54:10.598085Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:54:10.803708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:54:11.318950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:54:11.566343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:54:11.694024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:54:11.797281Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:54:11.831569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:54:11.883540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:54:11.976095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:54:12.400373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:54:16.706767Z | Info | Live bytes: 919.62MB Heap size: 2786.07MB +2024-07-08T11:55:16.711745Z | Info | Live bytes: 919.62MB Heap size: 2786.07MB +2024-07-08T11:56:16.755617Z | Info | Live bytes: 919.62MB Heap size: 2786.07MB +2024-07-08T11:56:26.855757Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:26.982973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:27.111858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:27.183190Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:27.325671Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:27.570521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:27.668077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:27.779283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:27.918540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:28.054922Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:28.400136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:31.022388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:49.932552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:50.620268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:51.273695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:51.542357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:51.917510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:52.543494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:53.886077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:54.477523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:55.839032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:56.177823Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:56.553144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:56:56.672798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:56:57.288024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:02.027873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:03.382075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:04.175560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:08.903344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:11.366251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:12.976934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:15.538432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:16.757042Z | Info | Live bytes: 969.83MB Heap size: 2786.07MB +2024-07-08T11:57:17.046643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:26.642585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:27.450579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:28.279293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:28.306510Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:28.874054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:29.471339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:30.108328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:30.906798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:31.836151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:32.625696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:32.731119Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:32.790553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:32.840443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.137217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.278908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.365666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:51.378077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.441849Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.702408Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.825741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.923916Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:51.946887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:52.016812Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:52.162224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:52.256386Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:52.380240Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:52.483680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:52.528602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:52.590894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:53.111116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:55.356697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:56.535471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:56.564453Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:56.667725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:56.763241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:56.836701Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:56.924206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:57:57.200383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:57:57.323565Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T11:57:58.045126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:10.426889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:16.759670Z | Info | Live bytes: 1206.90MB Heap size: 2823.82MB +2024-07-08T11:58:25.970703Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:26.106922Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:26.195645Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:26.451738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:26.829543Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:28.611966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:28.688649Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:28.759895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:28.856125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.019047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:29.074084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.180900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.274870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.395702Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.421589Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.619528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:29.642871Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.739297Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.855732Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:29.934338Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:30.083035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:30.180709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:30.328088Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:30.862508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:31.477624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:31.611097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:31.668023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:31.705073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:32.004454Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T11:58:32.237776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:38.645880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:39.258778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:43.788832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:46.458836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:50.167953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:50.761173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:54.419926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:55.058740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:56.294900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:57.028422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:57.848930Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:57.954719Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:58.009735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:58.086910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:58.216052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:58.410127Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:58.577942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:58:58.818030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:58.894613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:59.056564Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:58:59.306535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:02.668184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:03.999043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:04.920610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:06.297833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:06.869957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:10.926467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:12.512955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:13.362854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:14.779279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:16.763266Z | Info | Live bytes: 864.92MB Heap size: 2925.53MB +2024-07-08T11:59:23.922485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:24.552548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:25.429263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:27.447210Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:59:27.777943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:28.681425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T11:59:31.309010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:34.775144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:37.266491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:39.913455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T11:59:41.909663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:03.229984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:05.003351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:05.681467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:06.260430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:06.782453Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:00:12.879577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:14.912650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:15.812179Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:00:15.939476Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:00:16.013811Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:00:16.095870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:00:16.344844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:16.764579Z | Info | Live bytes: 970.29MB Heap size: 2925.53MB +2024-07-08T12:00:16.871925Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:00:17.073832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:00:17.424256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:17.680847Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:00:38.770149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:40.564507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:00:43.923417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:16.783897Z | Info | Live bytes: 1102.72MB Heap size: 2925.53MB +2024-07-08T12:01:41.867083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:42.616983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:01:42.782551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:01:42.978643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:43.107982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:01:43.367858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:01:43.582811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:44.333423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:44.915254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:45.568382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:46.520522Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:01:47.135897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:01.157960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:01.291819Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:01.365318Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:01.394527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:01.495718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:01.997557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:02.030230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:02.167866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:02.362746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:02.678028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:02.687816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:02.911404Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:03.004635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:03.106636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:03.217225Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:03.346235Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:03.424993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:04.207001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:04.689834Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:04.802119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:04.813112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:04.909569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:05.009677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:05.075819Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:05.393123Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:02:05.463822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:06.207633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:10.352685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:11.041447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:12.150901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:13.481521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:14.365608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:16.785340Z | Info | Live bytes: 807.99MB Heap size: 2952.79MB +2024-07-08T12:02:27.601502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:28.300327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:29.175599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:30.279757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:30.888237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:32.141280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:32.265469Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:32.339025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:32.493800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:32.565992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:32.665149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:32.738714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:32.778325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:33.105779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:33.304561Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:02:33.594863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:49.337111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:49.418918Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:02:50.116341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:59.583347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:02:59.837446Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:03:07.828040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:07.939342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:08.115704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:09.544375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:09.667040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:09.748185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:10.238984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:16.788429Z | Info | Live bytes: 901.45MB Heap size: 2952.79MB +2024-07-08T12:03:21.486540Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:22.071934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:22.359610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:23.433162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:23.636195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:23.696892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:23.773148Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:23.861120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:24.116874Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:24.264575Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:24.296328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:24.388961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:24.881579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:25.708173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:25.912047Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:26.210204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:26.302589Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:26.400762Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:26.413686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:26.695833Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:26.762444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:26.837362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:26.926424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:27.118400Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:27.192226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:27.374663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:27.452450Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:27.798396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:28.782411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:29.260574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:30.292616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:30.379648Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:30.756543Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:30.769127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:30.926854Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:30.998508Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:31.163275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:31.400275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:33.271326Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:33.672853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:33.764771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:03:34.115147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:34.276590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:34.404437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:34.485935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:03:34.539578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:04:16.814557Z | Info | Live bytes: 931.07MB Heap size: 2952.79MB +2024-07-08T12:04:19.260421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:04:20.562833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:04:21.973855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:16.816995Z | Info | Live bytes: 945.98MB Heap size: 2952.79MB +2024-07-08T12:05:34.298334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:34.384690Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:34.515934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:34.597478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:34.696729Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:34.749195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:34.837802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:35.318679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:35.962268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:36.541340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:36.880807Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:37.046839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:37.315444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:37.339662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:37.499785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:05:37.905050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:38.879756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:39.651485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:05:40.620638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:16.850150Z | Info | Live bytes: 1006.34MB Heap size: 2952.79MB +2024-07-08T12:06:24.716204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:06:24.803080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:06:24.815733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:25.069672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:06:25.176332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:06:25.264141Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:06:25.531135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:26.444213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:34.734090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:36.279035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:36.513465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:06:36.607769Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:06:37.033663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:38.459175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:39.755520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:40.433690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:41.090256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:41.995264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:42.105030Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:06:57.848017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:06:58.509926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:07:00.663221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:07:01.141592Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:07:16.866592Z | Info | Live bytes: 673.21MB Heap size: 3068.13MB +2024-07-08T12:07:27.903688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:07:28.084410Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:08:16.916656Z | Info | Live bytes: 679.22MB Heap size: 3068.13MB +2024-07-08T12:08:20.958748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:21.539651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:22.165667Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:22.442467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:22.532465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:22.673444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:22.937892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:23.171169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:23.745011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:24.277029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:24.458356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:24.481738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:25.093794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:25.664494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:26.347489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:28.447885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:35.194428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:38.660635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:38.788081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:39.360592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:53.664876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:53.807963Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:53.939935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:54.061790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:54.274537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:54.342675Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:54.930679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:55.532934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:55.697869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:55.861718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:56.333046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:56.428552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:56.600041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:56.859061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:57.072198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:57.233327Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:57.368605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:57.465724Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:57.568254Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:57.701932Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:57.717692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:08:57.821193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:57.917289Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:58.035436Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:58.307415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:08:58.324743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:09:01.877225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:09:16.928634Z | Info | Live bytes: 778.11MB Heap size: 3068.13MB +2024-07-08T12:10:09.566994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:10.250970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:10.880093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:11.186682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:11.365206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:11.502205Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:11.561929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:11.621080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:11.721369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:12.199584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:13.682737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:13.811713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:14.443571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:15.154343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:16.166576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:16.304384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:16.432260Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:16.447469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:16.538871Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:16.792684Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:16.929576Z | Info | Live bytes: 860.97MB Heap size: 3068.13MB +2024-07-08T12:10:17.003323Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:17.022890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:17.203929Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:17.417404Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:10:17.664971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:20.686204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:29.548402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:30.349555Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:31.168219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:41.641098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:42.384809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:50.521612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:10:51.733241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:11:16.932500Z | Info | Live bytes: 884.11MB Heap size: 3068.13MB +2024-07-08T12:11:54.407080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:11:54.570031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:11:54.677706Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:11:54.788691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:11:55.388042Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:11:55.414991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:11:56.055478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:11:56.803884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:11:57.336324Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:12:05.972348Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:06.413739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:16.935867Z | Info | Live bytes: 903.52MB Heap size: 3068.13MB +2024-07-08T12:12:47.408193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:48.025607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:54.801670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:54.980802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:55.156061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:55.279523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:55.851181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:56.406445Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:56.456210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:56.529302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:56.729735Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:56.838076Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:12:57.194505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:57.785550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:58.502839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:12:58.848918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:00.213842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:00.807940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:00.989958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:01.054618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:01.255870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:01.353938Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:01.640886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:04.637712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:04.838029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:05.004134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:05.123805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:05.275699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:13:05.738730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:10.824585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:10.904526Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:13:16.941661Z | Info | Live bytes: 956.22MB Heap size: 3068.13MB +2024-07-08T12:13:21.745441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:32.204051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:37.490560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:40.347009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:43.831582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:45.456951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:46.309303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:47.237645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:50.559692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:51.936395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:55.736459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:56.673756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:57.951207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:13:58.559634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:14:05.935480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:14:06.104020Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:14:11.114529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:14:11.795142Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:14:16.946577Z | Info | Live bytes: 995.78MB Heap size: 3068.13MB +2024-07-08T12:14:47.261140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:14:48.688045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:14:48.736807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:14:58.522992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:04.375557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:04.394087Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:05.117101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:05.724794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:06.394322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:07.014936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:07.624835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:08.668144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:10.489298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:13.034120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:13.436991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:13.801989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:13.862766Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:13.953654Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:14.438610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:15.030207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:16.924728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:16.947605Z | Info | Live bytes: 1029.31MB Heap size: 3068.13MB +2024-07-08T12:15:17.527484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:19.703409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:25.837267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:26.538571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:27.149254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:27.717390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:28.338554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:32.532784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:36.539248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:39.048546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:39.263961Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:15:39.961099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:48.268766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:49.324165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:49.454495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:49.478878Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:50.045198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:50.882692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:50.932936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:51.611493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:52.194513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:53.043039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:53.107851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:53.616618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:55.477857Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:15:55.994665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:56.679576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:57.433431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:15:58.386152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:00.753074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:05.835801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:06.610367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:11.329955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:13.103889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:16.952709Z | Info | Live bytes: 1098.10MB Heap size: 3068.13MB +2024-07-08T12:16:18.800263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:20.690270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:21.489241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:24.533475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:26.708761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:30.446091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:34.249467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:39.705509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:49.048822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:16:49.599235Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:16:50.296046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:17:16.963198Z | Info | Live bytes: 1133.48MB Heap size: 3068.13MB +2024-07-08T12:18:16.989131Z | Info | Live bytes: 1133.48MB Heap size: 3068.13MB +2024-07-08T12:18:50.148762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:13.542427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:16.990565Z | Info | Live bytes: 1127.90MB Heap size: 3068.13MB +2024-07-08T12:19:17.199085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:18.049641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:44.514649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:45.122070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:45.783174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:46.543242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:49.366022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:50.104636Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:19:54.994299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:55.588098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:56.290713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:57.004246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:59.039940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:19:59.390711Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:19:59.508602Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:19:59.524436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:19:59.744068Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:20:00.024119Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:20:00.105135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:00.713881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:01.140544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:20:01.444404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:07.138070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:07.951933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:11.871294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:13.926976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:14.789645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:15.808527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:16.992771Z | Info | Live bytes: 1197.01MB Heap size: 3068.13MB +2024-07-08T12:20:17.365556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:18.268044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:42.132515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:20:42.981077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:21:17.017785Z | Info | Live bytes: 1209.39MB Heap size: 3068.13MB +2024-07-08T12:22:17.077520Z | Info | Live bytes: 1209.39MB Heap size: 3068.13MB +2024-07-08T12:23:17.138399Z | Info | Live bytes: 1209.39MB Heap size: 3068.13MB +2024-07-08T12:23:39.171414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:39.787453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:40.367048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:43.308876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:44.223586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:45.087405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:46.570949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:47.177621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:47.766718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:49.274589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:49.880660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:52.528517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:54.672588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:55.662085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:23:59.244525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:24:00.905394Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:24:17.155638Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:25:17.191701Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:26:17.250813Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:27:17.275255Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:28:17.336433Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:29:17.360965Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:30:17.372596Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:31:17.432449Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:32:17.493435Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:33:17.528179Z | Info | Live bytes: 1245.46MB Heap size: 3068.13MB +2024-07-08T12:34:12.013835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:16.483618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:17.530574Z | Info | Live bytes: 1250.91MB Heap size: 3068.13MB +2024-07-08T12:34:18.631729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:19.400194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:19.453750Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:34:19.983811Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:34:20.477017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:21.155363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:27.473317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:34:27.653961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:34:27.728152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:48.868069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:34:49.652841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:14.132207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:16.483752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:17.317517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:17.532502Z | Info | Live bytes: 1279.75MB Heap size: 3068.13MB +2024-07-08T12:35:20.923391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:21.585985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:23.857870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:37.388047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:35:37.483750Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:35:38.193036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:36:05.120102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:36:17.540723Z | Info | Live bytes: 1287.70MB Heap size: 3068.13MB +2024-07-08T12:37:17.592610Z | Info | Live bytes: 1287.70MB Heap size: 3068.13MB +2024-07-08T12:37:31.123502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:37:36.926262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:37:37.126946Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:37:37.199139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:37:37.950031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:37:41.475447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:37:58.620529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:01.264564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:02.105207Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:38:09.218276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:09.458776Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:38:10.164008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:14.663662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:17.596494Z | Info | Live bytes: 646.33MB Heap size: 3068.13MB +2024-07-08T12:38:21.435162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:24.434659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:38:24.619078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:38:24.683546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:24.816058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:38:25.262569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:26.840913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:27.893147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:46.664585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:47.300689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:53.313484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:38:54.145054Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:39:07.504694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:39:08.017402Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:39:17.606851Z | Info | Live bytes: 668.30MB Heap size: 3068.13MB +2024-07-08T12:40:17.667749Z | Info | Live bytes: 668.30MB Heap size: 3068.13MB +2024-07-08T12:41:17.729036Z | Info | Live bytes: 668.30MB Heap size: 3068.13MB +2024-07-08T12:42:17.789987Z | Info | Live bytes: 668.30MB Heap size: 3068.13MB +2024-07-08T12:43:17.850572Z | Info | Live bytes: 668.30MB Heap size: 3068.13MB +2024-07-08T12:44:17.911427Z | Info | Live bytes: 668.30MB Heap size: 3068.13MB +2024-07-08T12:45:17.966071Z | Info | Live bytes: 668.30MB Heap size: 3068.13MB +2024-07-08T12:46:00.654818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:02.039733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:02.733377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:04.680877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:17.967019Z | Info | Live bytes: 687.17MB Heap size: 3068.13MB +2024-07-08T12:46:18.205570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:21.307598Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:46:21.633717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:23.834617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:27.270101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:42.267836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:42.301791Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:46:42.504637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:46:42.902288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:51.147008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:54.406525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:56.187181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:46:59.970034Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:00.102243Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:00.234979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:01.199437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:03.770117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:10.454498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:11.597840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:13.647188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:17.973075Z | Info | Live bytes: 853.65MB Heap size: 3068.13MB +2024-07-08T12:47:18.561896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:19.142414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:21.311877Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:21.600564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:26.992883Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:27.048324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:27.182462Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:27.484442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:27.639875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:29.353452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:42.806511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:47.782248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:53.057531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:53.322171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:53.375820Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:53.762842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:53.925298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:54.078324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:54.257132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:47:54.325518Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:47:58.223417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:48:17.988591Z | Info | Live bytes: 966.53MB Heap size: 3068.13MB +2024-07-08T12:49:18.049458Z | Info | Live bytes: 966.53MB Heap size: 3068.13MB +2024-07-08T12:50:08.353547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:50:11.692825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:50:18.052434Z | Info | Live bytes: 1002.68MB Heap size: 3068.13MB +2024-07-08T12:50:25.681234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:50:27.278040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:50:33.046400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:50:59.966622Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:00.104851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:00.318164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:00.900862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:01.577674Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:51:02.426511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:16.763677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:18.053683Z | Info | Live bytes: 1074.48MB Heap size: 3068.13MB +2024-07-08T12:51:18.137452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:18.799469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:19.610261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:20.316266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:21.187444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:21.526083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:22.137140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:22.291319Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:22.796452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:22.972193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:23.432897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:26.737928Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:26.781107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:26.849133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:27.580248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:28.568048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:29.500815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:55.276294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:55.951980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:51:56.024805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:56.659284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:57.307401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:58.059588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:58.675728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:51:59.582988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:00.508632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:01.212621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:01.258072Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:06.612367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:07.682272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:08.272732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:18.059968Z | Info | Live bytes: 1247.28MB Heap size: 3068.13MB +2024-07-08T12:52:31.655275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:32.254883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:32.826372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:33.631364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:38.161808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:38.619948Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:38.818634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:41.753090Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:41.899236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:42.026193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:42.085468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:42.289175Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:42.431763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:42.530133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:42.660694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:42.665037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:42.780470Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:42.923902Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:43.052908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:43.134163Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:43.245124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:43.285394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:43.967236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:44.169976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:44.231192Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:44.388410Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:44.436231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:44.471480Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:44.563725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:44.633903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:45.009488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:45.594999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:45.969109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:46.162109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:46.172784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:46.323162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:46.474381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:46.608621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:46.741446Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:46.858129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:46.909953Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:47.007957Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:47.106853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:47.163505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:52:47.453638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:47.509960Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:52:48.225919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:52:53.529656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:06.645537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:07.881883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:15.453065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:16.032297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:18.062923Z | Info | Live bytes: 876.08MB Heap size: 3068.13MB +2024-07-08T12:53:22.350617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:25.469371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:27.133736Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:53:27.829163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:31.104774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:34.246583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:34.913670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:53:36.630047Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:54:18.069641Z | Info | Live bytes: 916.38MB Heap size: 3068.13MB +2024-07-08T12:54:24.955725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:54:27.888494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:54:34.183227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:54:44.430944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:54:50.240870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:54:50.516197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:54:51.222738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:54:57.084535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:54:59.552602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:55:18.083611Z | Info | Live bytes: 946.38MB Heap size: 3068.13MB +2024-07-08T12:55:50.541693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:55:58.454589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:00.987089Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:01.271356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:01.400425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:01.895586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:02.071650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:02.189146Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:02.285593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:02.543435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:04.707555Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:07.003377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:18.090420Z | Info | Live bytes: 1012.99MB Heap size: 3068.13MB +2024-07-08T12:56:19.715770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:30.856255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:32.412403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:36.650577Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:36.672228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:36.706197Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:37.003773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:37.095013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T12:56:37.464785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:43.166641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:43.973034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:45.582332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T12:56:45.885090Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T12:56:46.724152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T13:37:28.044361Z | Info | Live bytes: 1056.14MB Heap size: 3068.13MB +2024-07-08T13:38:28.105670Z | Info | Live bytes: 1056.14MB Heap size: 3068.13MB +2024-07-08T13:38:37.897070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T13:39:28.145998Z | Info | Live bytes: 1066.37MB Heap size: 3068.13MB +2024-07-08T13:40:28.206965Z | Info | Live bytes: 1066.37MB Heap size: 3068.13MB +2024-07-08T13:41:28.243355Z | Info | Live bytes: 1066.37MB Heap size: 3068.13MB +2024-07-08T13:42:28.304562Z | Info | Live bytes: 1066.37MB Heap size: 3068.13MB +2024-07-08T13:43:28.328141Z | Info | Live bytes: 1066.37MB Heap size: 3068.13MB +2024-07-08T13:44:28.388846Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:45:28.450272Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:46:28.453398Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:47:28.485315Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:48:28.500132Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:49:28.529264Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:50:28.590264Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:50:36.603446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T13:51:28.644111Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:52:28.647506Z | Info | Live bytes: 1075.50MB Heap size: 3068.13MB +2024-07-08T13:53:08.898807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T13:53:28.667370Z | Info | Live bytes: 1101.44MB Heap size: 3068.13MB +2024-07-08T13:53:31.076227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T13:54:28.728436Z | Info | Live bytes: 1115.27MB Heap size: 3068.13MB +2024-07-08T13:55:28.767749Z | Info | Live bytes: 1115.27MB Heap size: 3068.13MB +2024-07-08T13:56:28.818997Z | Info | Live bytes: 1115.27MB Heap size: 3068.13MB +2024-07-08T13:57:28.875227Z | Info | Live bytes: 1115.27MB Heap size: 3068.13MB +2024-07-08T13:58:28.936618Z | Info | Live bytes: 1115.27MB Heap size: 3068.13MB +2024-07-08T13:59:28.958742Z | Info | Live bytes: 1115.27MB Heap size: 3068.13MB +2024-07-08T13:59:35.783756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:00:29.019836Z | Info | Live bytes: 1116.73MB Heap size: 3068.13MB +2024-07-08T14:00:34.592035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:01.407816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:02.600224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:03.459627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:03.824790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:04.337727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:11.063573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:11.162255Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:11.263108Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:11.571435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:12.499663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:13.428980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:14.087481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:15.378058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:15.542236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:15.854877Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:16.027721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:16.321587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:16.516565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:16.805748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:17.413324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:18.912612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:19.632097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:19.837971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:20.000887Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:20.098627Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:20.219476Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:20.378314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:20.488289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:22.754685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:23.989601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:27.991564Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:28.080185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:28.199573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:28.277738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-08T14:01:28.484291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-08T14:01:29.021989Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:02:29.078565Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:03:29.106426Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:04:29.126335Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:05:29.187271Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:06:29.247162Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:07:29.296233Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:08:29.351371Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:09:29.371345Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:10:29.432070Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:11:29.492931Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:12:29.553990Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:13:29.614838Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:14:29.675659Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:15:29.698984Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:16:29.749677Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:17:29.810871Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:18:29.816593Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:19:29.877271Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:20:29.888075Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:21:29.930918Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:22:29.991952Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:23:30.021326Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:24:30.067793Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:25:30.084548Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:26:30.130146Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:27:30.190887Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:28:30.251992Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:29:30.313043Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:30:30.371377Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:31:30.431204Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:32:30.485680Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:33:30.525291Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:34:30.585951Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:35:30.646752Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:36:30.677262Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:37:30.737271Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:38:30.767171Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:39:30.828036Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:40:30.855174Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:41:30.915813Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:42:30.955478Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:43:31.016666Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:44:31.033348Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:45:31.058197Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:46:31.060182Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:47:31.104965Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:48:31.166059Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:49:31.179880Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:50:31.240832Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:51:31.301646Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:52:31.362812Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:53:31.423159Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:54:31.483141Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:55:31.542279Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:56:31.603605Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:57:31.665128Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:58:31.726335Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T14:59:31.741384Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:00:31.800199Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:01:31.806241Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:02:31.867186Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:03:31.926801Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:04:31.958587Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:05:32.019819Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:06:32.080903Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:07:32.141908Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:08:32.169328Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:09:32.226908Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:10:32.269458Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:11:32.330401Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:12:32.391136Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:13:32.452349Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:14:32.513579Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:15:32.574439Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:16:32.634217Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:17:32.694950Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:18:32.756333Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:19:32.773570Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:20:32.813594Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:21:32.875198Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:22:32.936808Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:23:32.986749Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:24:33.047924Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:25:33.108298Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:26:33.165452Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:27:33.226132Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:28:33.286206Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:29:33.346874Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:30:33.352259Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:31:33.412205Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:32:33.461930Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:33:33.497538Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:34:33.502072Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:35:33.562155Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:36:33.622869Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:37:33.669483Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:38:33.675763Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:39:33.737204Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:40:33.750850Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:41:33.753544Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:42:33.787374Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:43:33.848795Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:44:33.910253Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:45:33.927852Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:46:33.930275Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:47:33.974344Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:48:34.001993Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:49:34.034394Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:50:34.073940Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:51:34.135188Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:52:34.165998Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:53:34.212659Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:54:34.274150Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:55:34.278221Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:56:34.339654Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:57:34.401047Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:58:34.421065Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T15:59:34.437444Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:00:34.469546Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:01:34.490161Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:02:34.499196Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:03:34.558632Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:04:34.597511Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:05:34.603799Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:06:34.650978Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:07:34.712292Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:08:34.773376Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:09:34.834323Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:10:34.850895Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:11:34.912205Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:12:34.973396Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:13:35.034591Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:14:35.068142Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:15:35.129379Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:16:35.190647Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:17:35.218677Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:18:35.250646Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:19:35.254470Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:20:35.295907Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:21:35.356267Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:22:35.416240Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:23:35.476264Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:24:35.536139Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:25:35.590130Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:26:35.651044Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:27:35.711213Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:28:35.771908Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:29:35.832975Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:30:35.883832Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:31:35.944119Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:32:36.004825Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:33:36.065329Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:34:36.074205Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:35:36.134410Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:36:36.136037Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:37:36.191977Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:38:36.230109Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:39:36.290225Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:40:36.350334Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:41:36.365508Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:42:36.418375Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:43:36.445391Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:44:36.506173Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:45:36.566400Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:46:36.627508Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:47:36.688540Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:48:36.749354Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:49:36.791492Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:50:36.852185Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:51:36.860529Z | Info | Live bytes: 1225.62MB Heap size: 3068.13MB +2024-07-08T16:52:12.223064Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-08T16:52:36.886585Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T16:53:36.947634Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T16:54:37.008964Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T16:55:37.070273Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T16:56:37.130284Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T16:57:37.187083Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T16:58:37.248000Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T16:59:37.308243Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:00:37.368901Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:01:37.429758Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:02:37.490565Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:03:37.501380Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:04:37.561355Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:05:37.570650Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:06:37.580367Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:07:37.641191Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:08:37.681294Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:09:37.742265Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:10:37.803238Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:11:37.863876Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:12:37.924837Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:13:37.933512Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:14:37.994528Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:15:38.030994Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:16:38.062816Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:17:38.067596Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:18:38.128247Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:19:38.189049Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:20:38.217317Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:21:38.244434Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:22:38.305436Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:23:38.365191Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:24:38.370213Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:25:38.430878Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:26:38.491193Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:27:38.500442Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:28:38.502693Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:29:38.563661Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:30:38.624224Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:31:38.639284Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:32:38.644089Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:33:38.704799Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:34:38.748166Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:35:38.809010Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:36:38.869980Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:37:38.930886Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:38:38.981779Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:39:39.042805Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:40:39.096178Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:41:39.156333Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:42:39.217504Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:43:39.278826Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:44:39.339783Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:45:39.400221Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:46:39.431038Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:47:39.468353Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:48:39.491756Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:49:39.493478Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:50:39.515496Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:51:39.576496Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:52:39.637429Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:53:39.642482Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:54:39.703644Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:55:39.765060Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:56:39.825338Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:57:39.867198Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:58:39.927360Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T17:59:39.988442Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:00:40.049636Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:01:40.110858Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:02:40.172283Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:03:40.233318Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:04:40.294231Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:05:40.325499Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:06:40.386800Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:07:40.447902Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:08:40.508872Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:09:40.569765Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:10:40.630872Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:11:40.669444Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:12:40.677367Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:13:40.738205Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:14:40.798312Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:15:40.859524Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:16:40.920373Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:17:40.981407Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:18:41.042633Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:19:41.103567Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:20:41.164397Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:21:41.225247Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:22:41.286303Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:23:41.347408Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:24:41.408323Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:25:41.469374Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:26:41.530270Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:27:41.591350Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:28:41.652320Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:29:41.713173Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:30:41.750715Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:31:41.789327Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:32:41.839231Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:33:41.899738Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:34:41.960801Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:35:41.989436Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:36:42.050445Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:37:42.111813Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:38:42.173146Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:39:42.234342Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:40:42.295663Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:41:42.356986Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:42:42.418301Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:43:42.479501Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:44:42.485365Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:45:42.546310Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:46:42.607353Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:47:42.668287Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:48:42.729528Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:49:42.791705Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:50:42.798166Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:51:42.859094Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:52:42.919775Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:53:42.981116Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:54:43.042287Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:55:43.103444Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:56:43.157447Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:57:43.190884Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:58:43.237526Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T18:59:43.245428Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:00:43.301526Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:01:43.311931Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:02:43.373269Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:03:43.426733Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:04:43.468552Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:05:43.481620Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:06:43.501197Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:07:43.562335Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:08:43.623503Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:09:43.653462Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:10:43.689422Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:11:43.724592Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:12:43.749467Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:13:43.792994Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:14:43.854312Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:15:43.909604Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:16:43.970976Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:17:44.032261Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:18:44.093715Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:19:44.155151Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:20:44.216341Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:21:44.249177Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:22:44.272077Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:23:44.333472Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:24:44.394886Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:25:44.456280Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:26:44.517683Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:27:44.579078Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:28:44.640427Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:29:44.701880Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:30:44.704331Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:31:44.737425Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:32:44.747942Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:33:44.750225Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:34:44.774978Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:35:44.801197Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:36:44.832469Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:37:44.893360Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:38:44.902094Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:39:44.963929Z | Info | Live bytes: 1228.45MB Heap size: 3068.13MB +2024-07-08T19:40:12.017878Z | Info | LSP: received shutdown +2024-07-08T19:40:12.021722Z | Error | Got EOF +2024-07-09 06:58:13.7590000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-09 06:58:13.7600000 [client] INFO Finding haskell-language-server +2024-07-09 06:58:13.7640000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:13.7640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:13.7720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-09 06:58:14.1190000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:14.1190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:14.1240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-09 06:58:14.3010000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:14.3010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:14.3070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-09 06:58:14.4330000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:14.4330000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:14.4400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-09 06:58:14.5840000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:14.5840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:14.5910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-09 06:58:14.6150000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:14.6150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:14.6220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-09 06:58:14.6560000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:14.6560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:14.6630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-09 06:58:14.6850000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-09 06:58:14.8460000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:14.8460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:14.8550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-09 06:58:14.9820000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-09 06:58:14.9830000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-09 06:58:23.9040000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-09 06:58:23.9860000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-09 06:58:23.9860000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:23.9860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:23.9960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-09 06:58:24.1840000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:24.1840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:24.1890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-09 06:58:24.2040000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:24.2040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:24.2080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-09 06:58:24.2220000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:24.2220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:24.2280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-09 06:58:24.2440000 [client] INFO Checking for ghcup installation +2024-07-09 06:58:24.2450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 06:58:24.2560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-09 06:58:24.5650000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-09 06:58:24.5660000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-09 06:58:24.5670000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-09 06:58:24.5670000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-09 06:58:24.5670000 [client] INFO server environment variables: +2024-07-09 06:58:24.5670000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-09 06:58:24.5670000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-09 06:58:24.5670000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-09 06:58:24.5690000 [client] INFO Starting language server +2024-07-09T06:58:36.855672Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-09T06:58:36.858263Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-09T06:58:36.858759Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-09T06:58:36.864520Z | Info | Logging heap statistics every 60.00s +2024-07-09T06:58:36.878805Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-09T06:58:36.879317Z | Info | Starting server +2024-07-09T06:58:36.897135Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-09T06:58:36.968308Z | Info | Started LSP server in 0.09s +2024-07-09T06:58:38.740134Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-09T06:58:38.741767Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-09T06:58:39.372163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T06:58:39.372402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T06:58:40.457066Z | Info | Load cabal cradle using single file +2024-07-09T06:58:41.455724Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT13902-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-09T06:58:46.097164Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-1615d6206a80f4a0e31ef63d6e69b655fd28231c +2024-07-09T06:58:46.103425Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-09T06:59:36.914737Z | Info | Live bytes: 236.57MB Heap size: 1391.46MB +2024-07-09T07:00:13.539795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:00:14.108158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:00:16.891488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:00:16.924194Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:00:17.980933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:00:18.547366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:00:36.920691Z | Info | Live bytes: 484.96MB Heap size: 1871.71MB +2024-07-09T07:01:15.823485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:01:29.990646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:01:36.923196Z | Info | Live bytes: 482.44MB Heap size: 1871.71MB +2024-07-09T07:01:41.301988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:01:41.374447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:01:41.522871Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:01:41.984165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:02:36.973708Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:03:36.993997Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:04:37.055550Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:05:37.058138Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:06:37.119335Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:07:37.180519Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:08:37.199557Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:09:37.260622Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:10:37.317943Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:11:37.326983Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:12:37.369351Z | Info | Live bytes: 495.30MB Heap size: 1871.71MB +2024-07-09T07:12:57.084003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:13:28.648187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:13:31.817422Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:13:31.847240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:13:31.986556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:13:32.063919Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:13:32.444981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:13:32.913787Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:13:33.169606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:13:33.722509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:13:34.378646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:13:37.373667Z | Info | Live bytes: 549.56MB Heap size: 1871.71MB +2024-07-09T07:14:31.623925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:14:37.375488Z | Info | Live bytes: 737.30MB Heap size: 1896.87MB +2024-07-09T07:14:44.348230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:15:37.394366Z | Info | Live bytes: 791.63MB Heap size: 2003.83MB +2024-07-09T07:16:13.589821Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:16:37.417884Z | Info | Live bytes: 563.04MB Heap size: 2349.86MB +2024-07-09T07:17:03.577989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:17:37.424059Z | Info | Live bytes: 600.64MB Heap size: 2349.86MB +2024-07-09T07:17:51.001284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:18:37.443804Z | Info | Live bytes: 618.87MB Heap size: 2349.86MB +2024-07-09T07:19:37.505866Z | Info | Live bytes: 618.87MB Heap size: 2349.86MB +2024-07-09T07:20:32.698814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:20:37.511978Z | Info | Live bytes: 618.87MB Heap size: 2349.86MB +2024-07-09T07:20:41.821266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:21:01.159839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:21:37.513153Z | Info | Live bytes: 628.81MB Heap size: 2349.86MB +2024-07-09T07:21:58.101182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:22:37.538007Z | Info | Live bytes: 638.30MB Heap size: 2349.86MB +2024-07-09T07:22:39.747613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:22:48.638198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:22:49.027895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:22:49.612181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:22:50.397948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:22:51.877083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:23:08.492077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:23:08.582565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:23:08.736554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:23:08.958829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:23:09.110639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:23:09.187492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:23:09.205545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T07:23:09.768826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:23:37.562479Z | Info | Live bytes: 671.28MB Heap size: 2349.86MB +2024-07-09T07:24:37.608407Z | Info | Live bytes: 671.28MB Heap size: 2349.86MB +2024-07-09T07:25:37.663420Z | Info | Live bytes: 671.28MB Heap size: 2349.86MB +2024-07-09T07:26:37.667831Z | Info | Live bytes: 671.28MB Heap size: 2349.86MB +2024-07-09T07:26:40.451035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:26:41.726862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:26:44.787413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:26:50.100733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T07:27:37.711835Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:28:37.773184Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:29:37.799105Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:30:37.860225Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:31:37.874893Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:32:37.889164Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:33:37.950225Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:34:38.010716Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:35:38.019217Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:36:38.051472Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:37:38.071967Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:38:38.084147Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:39:38.113678Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:40:38.173650Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:41:38.234523Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:42:38.294715Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:43:38.311576Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:44:38.367729Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:45:38.379637Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:46:38.397344Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:47:38.403779Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:48:38.457404Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:49:38.517694Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:50:38.578532Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:51:38.639757Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:52:38.662495Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:53:38.723750Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:54:38.741109Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:55:38.801582Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:56:38.836349Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:57:38.839867Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:58:38.894447Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T07:59:38.956294Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:00:39.018512Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:01:39.079972Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:02:39.141347Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:03:39.202634Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:04:39.208457Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:05:39.223962Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:06:39.242416Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:07:39.298255Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:08:39.359851Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:09:39.420834Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:10:39.474668Z | Info | Live bytes: 701.60MB Heap size: 2349.86MB +2024-07-09T08:11:23.844954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:24.541009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:25.208763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:26.496049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:27.545259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:36.690794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:37.379640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:38.072659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:38.925165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:11:39.476570Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:12:39.524028Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:13:39.570797Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:14:39.575844Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:15:39.585506Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:16:39.639732Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:17:39.671807Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:18:39.692445Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:19:39.753935Z | Info | Live bytes: 777.09MB Heap size: 2349.86MB +2024-07-09T08:20:21.904271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:20:39.771723Z | Info | Live bytes: 816.25MB Heap size: 2349.86MB +2024-07-09T08:20:54.803242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:20:55.850149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:20:55.897137Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:20:56.468363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:20:56.931831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:21:39.815682Z | Info | Live bytes: 821.41MB Heap size: 2349.86MB +2024-07-09T08:22:13.324109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:13.362938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:14.246191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:14.758874Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:14.875892Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:14.967675Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:15.154367Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:15.216024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:15.237171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:15.663209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:15.840401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:15.922609Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:16.031111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:16.139309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:17.051868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:20.931488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:39.834918Z | Info | Live bytes: 865.59MB Heap size: 2349.86MB +2024-07-09T08:22:42.407544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:44.030346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:45.019275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:45.184208Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:45.379994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:45.958093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:46.713099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:47.008448Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:47.269598Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:47.291763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:22:47.371617Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:47.529893Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:22:47.846031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:02.919679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:04.869349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:05.772116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:06.513120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:12.150079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:16.271046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:16.903819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:18.194897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:19.658857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:39.856198Z | Info | Live bytes: 962.34MB Heap size: 2370.83MB +2024-07-09T08:23:49.394117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:50.369921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:51.207480Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:23:51.224691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:51.532187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:23:51.670633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:23:51.851739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:23:52.019630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:23:53.037819Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:23:53.150698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:23:53.438189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:03.381655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:04.300578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:09.976244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:13.486738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:14.126200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:22.006541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:23.130825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:25.190424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:31.937510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:32.355302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:32.564565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:32.646498Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:32.729541Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:32.827743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:32.882073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:33.985113Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:34.176826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:34.332486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:34.443743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:34.454040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:35.176894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:35.348864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:35.479442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:35.651217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:35.805151Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:36.282619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:39.169324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:39.321738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:39.400776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:24:39.652593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:39.858046Z | Info | Live bytes: 1003.30MB Heap size: 2540.70MB +2024-07-09T08:24:47.174043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:49.638823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:51.100635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:51.713120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:52.310740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:56.450758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:24:59.876465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:18.832817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:19.532076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:21.672369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:23.510445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:24.420052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:25.162614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:25.868903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:27.278300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:29.957545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:30.292276Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T08:25:31.161190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:25:39.859699Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:26:39.904058Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:27:39.926579Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:28:39.988059Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:29:39.995356Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:30:40.057027Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:31:40.118091Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:32:40.120177Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:33:40.123834Z | Info | Live bytes: 1041.53MB Heap size: 2634.02MB +2024-07-09T08:34:27.221984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:34.971258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:36.063270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:36.279509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:34:36.685088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:37.041506Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:34:37.248592Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:34:37.332252Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:34:37.539816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:38.312887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:38.890890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:39.514871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:40.126180Z | Info | Live bytes: 1059.82MB Heap size: 2663.38MB +2024-07-09T08:34:40.454723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:45.769205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:34:57.459926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:01.709842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:04.848460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:05.409416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:05.970872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:06.528974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:07.199529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:07.923981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:08.622336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:09.226884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:09.801095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:10.408976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:11.070977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:11.872519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:13.274018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:14.046128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:16.812836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:18.399333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:24.439987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:25.378846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:25.969189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:36.739323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:39.547556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:40.127470Z | Info | Live bytes: 1112.01MB Heap size: 2779.77MB +2024-07-09T08:35:40.189398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:42.846044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:46.955726Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:47.510418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:49.959193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:51.086856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:51.987763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:53.891632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:35:54.456271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:08.284861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:08.870613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:10.030310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:13.409251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:14.707766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:15.605337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:17.662934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:19.430501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:21.851446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:22.401929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:22.976227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:23.603373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:25.029619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:25.611647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:26.895151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:27.270295Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T08:36:27.955702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:32.227924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:36.024871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:40.133099Z | Info | Live bytes: 653.76MB Heap size: 2779.77MB +2024-07-09T08:36:46.778717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:48.792952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:36:51.645939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:08.227253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:09.271324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:09.855938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:15.361788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:16.101581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:17.177035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:22.061440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:23.776343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:28.613502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:30.132383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:31.682344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:32.365348Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:37:32.552252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:32.960281Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:37:33.406732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:35.382293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:40.139125Z | Info | Live bytes: 744.29MB Heap size: 2779.77MB +2024-07-09T08:37:44.028825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:37:44.137861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:37:44.300343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:37:44.500044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:45.020693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:37:45.078760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:45.711518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:46.427903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:47.363478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:37:48.167907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:05.898310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:38.183943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:38.900334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:40.140267Z | Info | Live bytes: 797.80MB Heap size: 2779.77MB +2024-07-09T08:38:40.267544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:40.685490Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:38:40.889122Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:43.184345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:46.590527Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:38:46.611603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:48.104794Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:38:48.300814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:53.546312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:54.616512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:38:55.888762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:05.582091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:06.153826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:06.423494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:13.770276Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:13.848435Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:13.979879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:14.066921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:14.098598Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:14.613603Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:14.759395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:14.867062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:15.344805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:25.634847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:26.589981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:27.632004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:28.457451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:28.889084Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T08:39:29.572450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:31.513171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:32.825178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:34.644903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:40.146657Z | Info | Live bytes: 966.59MB Heap size: 2779.77MB +2024-07-09T08:39:43.147184Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:43.232892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:43.545083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:43.998419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:48.032856Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:48.216509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:48.514704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:49.174261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:49.262241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:49.323927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:49.714069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:49.893492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:50.448531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:51.387665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:51.983398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:52.017583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:52.481356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:39:52.943544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:58.798677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:39:59.631229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:04.537318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:04.970822Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:40:05.172437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:05.978173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:40.176119Z | Info | Live bytes: 1067.42MB Heap size: 2779.77MB +2024-07-09T08:40:49.034483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:49.703766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:50.771136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:57.838990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:40:57.844664Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T08:41:09.318359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:09.883256Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T08:41:28.646779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:41:28.889237Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:41:28.962052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:29.203843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:41:29.475721Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:41:29.655865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:30.285784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:36.221509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:40.181895Z | Info | Live bytes: 1128.35MB Heap size: 2779.77MB +2024-07-09T08:41:44.873506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:46.422644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:49.831309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:57.949464Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:41:58.084237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:59.050703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:59.446210Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:41:59.656812Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:41:59.912706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:41:59.912808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:42:00.048069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:42:00.512478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:04.025635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:06.928167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:08.554455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:09.986985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:10.234506Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:42:10.556815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:12.638640Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:42:12.802447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:13.041462Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:42:13.434954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:15.118833Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:42:15.556117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:15.606982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T08:42:26.368862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:27.115419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:28.822259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:29.835752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:39.912533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:40.184754Z | Info | Live bytes: 688.87MB Heap size: 2779.77MB +2024-07-09T08:42:40.521022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:41.475026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:41.708349Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T08:42:44.575625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:46.212662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:42:47.346666Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T08:42:48.035868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:43:40.234239Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:44:40.254570Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:45:40.270646Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:46:40.297482Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:47:40.350922Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:48:40.412112Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:49:40.452842Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:50:40.458667Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:51:40.474571Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:52:40.534523Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:53:40.595129Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:54:40.655619Z | Info | Live bytes: 705.59MB Heap size: 2779.77MB +2024-07-09T08:55:38.097280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:55:40.658878Z | Info | Live bytes: 702.67MB Heap size: 2779.77MB +2024-07-09T08:56:17.411198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:56:40.719689Z | Info | Live bytes: 702.67MB Heap size: 2779.77MB +2024-07-09T08:57:40.744932Z | Info | Live bytes: 702.67MB Heap size: 2779.77MB +2024-07-09T08:58:35.149901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T08:58:40.747975Z | Info | Live bytes: 736.47MB Heap size: 2779.77MB +2024-07-09T08:59:40.808516Z | Info | Live bytes: 748.60MB Heap size: 2779.77MB +2024-07-09T09:00:20.579798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:00:40.869437Z | Info | Live bytes: 764.17MB Heap size: 2779.77MB +2024-07-09T09:01:40.889761Z | Info | Live bytes: 764.17MB Heap size: 2779.77MB +2024-07-09T09:02:40.894013Z | Info | Live bytes: 764.17MB Heap size: 2779.77MB +2024-07-09T09:03:40.900485Z | Info | Live bytes: 767.78MB Heap size: 2779.77MB +2024-07-09T09:04:01.466503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:02.455129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:03.868790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:04.500405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:05.484712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:06.413447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:07.027086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:07.590805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:08.149659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:10.772262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:10.949188Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:11.032071Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:11.269086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:11.303748Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:11.373796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:11.486494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:11.889019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:12.093599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:12.257129Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:12.411406Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:12.608702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:12.964983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:13.105778Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:13.230217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:13.473683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:13.569276Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:13.774052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:14.075792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:14.640372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:17.348467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:40.920858Z | Info | Live bytes: 814.38MB Heap size: 2779.77MB +2024-07-09T09:04:52.882280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:53.458679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:54.979165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:56.052688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:56.300886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:56.626546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:57.218492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:58.090770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:04:58.197454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:58.789524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:04:59.563598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:00.187080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:00.764087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:01.822475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:01.953746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:02.371629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:02.585083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:03.094948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:04.061730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:04.969901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:05.458830Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:05.508848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:05.568047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:10.303044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:15.668173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:16.682218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:18.033545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:22.976641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:25.801059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:27.798526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:28.794819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:31.500595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:32.378774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:32.529287Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:33.039236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:34.222405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:35.297680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:36.463772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:36.546807Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:36.809225Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:36.949624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:37.003424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:37.062528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:37.138007Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:37.400873Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:37.621258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:37.652857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:37.858045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:38.342944Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:38.371673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:38.459241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:38.975809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:39.546196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:39.845509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:39.909079Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:40.012385Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:40.248801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:40.355152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:40.379633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:05:40.922382Z | Info | Live bytes: 1085.11MB Heap size: 2821.72MB +2024-07-09T09:05:40.979032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:41.798097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:43.710462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:05:44.671173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:03.901728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:04.626156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:05.474390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:06:05.704625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:05.802415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:06:05.961239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:06:06.087802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:06:06.304143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:06.337569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:06:07.150297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:07.708776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:11.483792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:06:40.947966Z | Info | Live bytes: 675.80MB Heap size: 2855.27MB +2024-07-09T09:07:41.009224Z | Info | Live bytes: 675.80MB Heap size: 2855.27MB +2024-07-09T09:07:59.750843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:00.008659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:00.037525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:00.116899Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:00.613702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:00.693770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:00.808145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:01.189598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:03.526828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:04.136394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:04.393981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:04.488183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:04.613971Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:04.877536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:05.150898Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:05.602480Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:05.642879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:05.729778Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:06.175687Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:06.234150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:06.420246Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:06.500151Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:06.574716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:06.906640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:08.030698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:13.941540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:14.062291Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:14.158367Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:14.245460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:14.462446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:15.709462Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T09:08:15.751053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:16.453197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:20.402999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:33.383727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:34.025330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:34.036563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:34.737318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:35.999500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:36.712006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:37.175076Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:37.237776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:37.318147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:08:37.358933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:38.532129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:39.084349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:41.012775Z | Info | Live bytes: 991.95MB Heap size: 2855.27MB +2024-07-09T09:08:45.363321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:47.355735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:48.883739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:08:52.633947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:07.215743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:09:07.289583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:09:07.399290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:09:07.664296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:08.338853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:09:08.436170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:09.387451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:17.723595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:18.331188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:21.936847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:23.305106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:24.243953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:26.687898Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T09:09:26.707135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:27.406947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:09:41.015657Z | Info | Live bytes: 1068.18MB Heap size: 2855.27MB +2024-07-09T09:10:41.066324Z | Info | Live bytes: 1068.18MB Heap size: 2855.27MB +2024-07-09T09:10:57.874473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:10:59.098129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:10:59.966580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:00.690251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:00.832220Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:01.341200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:02.044083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:02.674898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:03.415793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:04.097902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:04.997305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:05.551484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:06.868838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:09.034709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:09.622729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:14.868679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:17.370293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:17.432578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:17.582966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:17.992277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:21.239027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:24.106565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:25.377073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:26.500169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:27.552441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:28.382710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:28.460080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:28.966533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:29.821133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:30.571788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:31.409866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:31.861370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:31.926967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.084621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.126442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.221896Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.307071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:32.411974Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.550563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.705357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.781487Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.838780Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:32.924809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:32.942292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:33.814536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:34.665565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:39.036028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:41.069471Z | Info | Live bytes: 1132.70MB Heap size: 3012.56MB +2024-07-09T09:11:41.952130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:44.024208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:44.105619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:44.251413Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T09:11:44.589564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:11:46.455903Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T09:11:47.184587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:12:41.074944Z | Info | Live bytes: 597.71MB Heap size: 3012.56MB +2024-07-09T09:13:41.104970Z | Info | Live bytes: 607.02MB Heap size: 3012.56MB +2024-07-09T09:13:42.698462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:13:49.436866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:13:57.657641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:14:13.104445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:14:18.587885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:14:41.112903Z | Info | Live bytes: 712.60MB Heap size: 3012.56MB +2024-07-09T09:15:41.140588Z | Info | Live bytes: 712.60MB Heap size: 3012.56MB +2024-07-09T09:16:41.201300Z | Info | Live bytes: 712.60MB Heap size: 3012.56MB +2024-07-09T09:17:41.203045Z | Info | Live bytes: 712.60MB Heap size: 3012.56MB +2024-07-09T09:18:41.206898Z | Info | Live bytes: 712.60MB Heap size: 3012.56MB +2024-07-09T09:19:41.268266Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:20:41.330013Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:21:41.391322Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:22:41.453181Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:23:41.514660Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:24:41.576018Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:25:41.637344Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:26:41.698523Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:27:41.759783Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:28:41.799876Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:29:41.860578Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:30:41.920664Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:31:41.981748Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:32:42.042461Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:33:42.103013Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:34:42.127538Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:35:42.187590Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:36:42.248276Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:37:42.280772Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:38:42.308904Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:39:42.361663Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:40:42.421450Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:41:42.427203Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:42:42.481297Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:43:42.497712Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:44:42.558621Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:45:42.614148Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:46:42.660922Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:47:42.721522Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:48:42.775695Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:49:42.836508Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:50:42.897226Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:51:42.958075Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:52:42.976793Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:53:43.005969Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:54:43.059362Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:55:43.093591Z | Info | Live bytes: 715.27MB Heap size: 3012.56MB +2024-07-09T09:56:43.153684Z | Info | Live bytes: 716.97MB Heap size: 3012.56MB +2024-07-09T09:56:45.476088Z | Info | Cradle path: cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/Ord.hs +2024-07-09T09:56:45.476522Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-09T09:56:45.520523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T09:56:47.117853Z | Info | Load cabal cradle using single file +2024-07-09T09:56:48.039045Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:test:cardano-api-test + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT13902-21 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-09T09:56:58.818811Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/main-dc43488629f1d14bba6bb01a2a59684a12b6e207-dc43488629f1d14bba6bb01a2a59684a12b6e207 +2024-07-09T09:56:58.819056Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-dc43488629f1d14bba6bb01a2a59684a12b6e207 +2024-07-09T09:56:58.825615Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-8.49.0.0-inplace-internal + , main-dc43488629f1d14bba6bb01a2a59684a12b6e207 ] +2024-07-09T09:57:43.183920Z | Info | Live bytes: 1074.65MB Heap size: 3088.06MB +2024-07-09T09:58:43.240839Z | Info | Live bytes: 1074.65MB Heap size: 3088.06MB +2024-07-09T09:59:43.259049Z | Info | Live bytes: 1074.65MB Heap size: 3088.06MB +2024-07-09T10:00:43.319991Z | Info | Live bytes: 1074.65MB Heap size: 3088.06MB +2024-07-09T10:01:43.328046Z | Info | Live bytes: 1074.65MB Heap size: 3088.06MB +2024-07-09T10:02:43.354189Z | Info | Live bytes: 1074.65MB Heap size: 3088.06MB +2024-07-09T10:03:43.415269Z | Info | Live bytes: 1074.65MB Heap size: 3088.06MB +2024-07-09T10:04:24.651325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:04:43.434598Z | Info | Live bytes: 1078.13MB Heap size: 3088.06MB +2024-07-09T10:05:43.474618Z | Info | Live bytes: 1096.55MB Heap size: 3088.06MB +2024-07-09T10:06:43.535747Z | Info | Live bytes: 1096.75MB Heap size: 3088.06MB +2024-07-09T10:06:52.323227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:07:43.557132Z | Info | Live bytes: 1104.96MB Heap size: 3088.06MB +2024-07-09T10:08:43.572487Z | Info | Live bytes: 1104.96MB Heap size: 3088.06MB +2024-07-09T10:09:43.590567Z | Info | Live bytes: 1104.96MB Heap size: 3088.06MB +2024-07-09T10:10:37.303251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:37.803691Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:10:37.872905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:38.155917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:10:38.319538Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:10:38.663722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:38.712544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:10:39.188480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:39.945464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:40.551625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:40.744510Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:10:41.145462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:41.834403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:42.477214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:43.592190Z | Info | Live bytes: 1014.61MB Heap size: 3121.61MB +2024-07-09T10:10:43.654858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:44.286058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:44.975245Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:45.639816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:47.914368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:48.635070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:49.254196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:49.961078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:50.281128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:10:50.747985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:10:51.532836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:09.872001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:10.622545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:10.912908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:11:11.310077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:11.964528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:13.139661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:25.284198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:25.943949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:26.544397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:28.680242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:30.348716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:30.454611Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:11:30.930953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:32.025907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:33.156975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:33.923735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:38.001529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:39.386518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:40.483083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:42.877396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:43.457559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:43.593274Z | Info | Live bytes: 1041.82MB Heap size: 3121.61MB +2024-07-09T10:11:44.108731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:45.104120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:46.221824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:46.838276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:47.812820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:48.403554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:49.011107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:49.786490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:50.491916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:51.846083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:52.497801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:53.445927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:54.447917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:59.366798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:11:59.965709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:00.525847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:07.218569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:07.830784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:08.422397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:09.158108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:09.764900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:10.330414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:10.929784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:11.497278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:12:43.621744Z | Info | Live bytes: 1062.89MB Heap size: 3121.61MB +2024-07-09T10:13:43.624609Z | Info | Live bytes: 1062.89MB Heap size: 3121.61MB +2024-07-09T10:14:06.866897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:19.595672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:23.585243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:24.351495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:24.959193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:24.980350Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:14:25.045682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:14:25.548137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:27.705247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:31.732403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:32.786711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:35.247271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:35.839322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:38.684592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:39.250488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:40.468837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:41.254123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:42.964916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:43.240761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:14:43.284690Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:14:43.363358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:14:43.625845Z | Info | Live bytes: 1144.75MB Heap size: 3121.61MB +2024-07-09T10:14:43.733343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:14:53.469767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:04.714412Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T10:15:05.319563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:06.453008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:07.017056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:08.180289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:08.805559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:09.380284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:10.205397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:10.833979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:11.538440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:12.496322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:13.077759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:29.752155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:30.430758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:31.078816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:31.770833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:32.445302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:34.431060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:35.747428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:36.480239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:37.325286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:37.956466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:38.629227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:39.770805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:41.475980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:43.627197Z | Info | Live bytes: 1255.80MB Heap size: 3121.61MB +2024-07-09T10:15:43.971407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:44.042361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:15:44.121842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T10:15:44.550553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:45.146825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:45.808928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:46.884601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:47.583744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:48.616599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:49.216042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:49.910293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:50.501458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:51.099092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:51.898913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:15:52.099508Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T10:15:52.827863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T10:16:43.631846Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:17:43.693076Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:18:43.754031Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:19:43.815201Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:20:43.876360Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:21:43.937281Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:22:43.998577Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:23:44.059880Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:24:44.121341Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:25:44.182839Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:26:44.244127Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:27:44.305158Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:28:44.366546Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:29:44.428026Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:30:44.439973Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:31:44.501289Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:32:44.562833Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:33:44.603005Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:34:44.644556Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:35:44.693747Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:36:44.755061Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:37:44.802321Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:38:44.815832Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:39:44.876829Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:40:44.911294Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:41:44.946730Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:42:44.951869Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:43:44.983844Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:44:45.015878Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:45:45.077041Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:46:45.107081Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:47:45.168498Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:48:45.228582Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:49:45.289252Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:50:45.313570Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:51:45.316615Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:52:45.377954Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:53:45.438707Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:54:45.485451Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:55:45.546676Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:56:45.607928Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:57:45.623900Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:58:45.682511Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T10:59:45.739565Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:00:45.800362Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:01:45.811176Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:02:45.872272Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:03:45.928228Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:04:45.987144Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:05:46.048546Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:06:46.078461Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:07:46.080019Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:08:46.103993Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:09:46.149274Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:10:46.163151Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:11:46.209719Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:12:46.231939Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:13:46.235704Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:14:46.265072Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:15:46.281625Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:16:46.327760Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:17:46.388861Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:18:46.439560Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:39:23.650018Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:40:23.688411Z | Info | Live bytes: 1317.18MB Heap size: 3126.85MB +2024-07-09T11:41:23.690398Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:42:23.748423Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:43:23.808259Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:44:23.814958Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:45:23.875457Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:46:23.935466Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:47:23.963309Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:48:24.023290Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:49:24.083996Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:50:24.145291Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:51:24.191031Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:52:24.231807Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:53:24.292493Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:54:24.353463Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:55:24.361408Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:56:24.422370Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:57:24.483549Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:58:24.544435Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T11:59:24.605453Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T12:00:24.666383Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T12:01:24.727320Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T12:02:24.788258Z | Info | Live bytes: 1313.39MB Heap size: 3126.85MB +2024-07-09T12:03:14.151237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:19.551610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:19.676806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:19.870474Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:20.177024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:20.177088Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:20.347429Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:20.470918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:20.539727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:20.611155Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:20.798455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:20.840963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:21.369196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:21.509387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:21.689505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:21.868369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:22.944355Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:23.223674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:24.790672Z | Info | Live bytes: 1369.69MB Heap size: 3174.04MB +2024-07-09T12:03:26.712494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:26.787369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:26.856237Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:27.060464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:27.729965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:30.271940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:30.382939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:30.455347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:30.972983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:31.074031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:31.194081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:31.314927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:31.455057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:34.746316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:35.030674Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:35.237622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:35.429774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:35.929686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:36.215507Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:36.478927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:36.689251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:36.860743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:37.058928Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:37.183862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:37.292628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:37.895470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:38.475868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:38.692699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:39.180802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:40.584155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:41.381567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:41.483290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:41.542945Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:41.622579Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:03:41.969204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:43.727602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:44.292158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:44.944301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:45.596197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:03:46.423754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:19.966862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:20.072978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:20.141781Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:20.332214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:20.408700Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:20.467217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:20.696844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:20.898702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:21.295418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:21.709860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:22.457667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:23.663585Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:23.901960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:24.242808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:24.454788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:24.538147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:24.614205Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:24.748984Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:24.754935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:24.792266Z | Info | Live bytes: 1489.44MB Heap size: 3390.05MB +2024-07-09T12:04:25.035456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:25.545556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:26.432231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:27.041741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:28.483433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:29.210092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:29.775034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:30.633454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:31.380621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:31.585669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:31.896850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:31.983303Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:32.246516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:32.400798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:32.561937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:32.628012Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:32.907990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:33.240581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:33.556952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:33.753010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:34.302035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:35.092904Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:35.738618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:35.887431Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:36.123950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:36.402428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:37.472390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:38.591955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:39.445849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:39.983311Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:40.096911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:40.131693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:04:40.645492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:41.253939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:43.711475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:44.361665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:45.038438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:04:45.648169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:05:24.794312Z | Info | Live bytes: 1573.81MB Heap size: 3490.71MB +2024-07-09T12:06:24.852877Z | Info | Live bytes: 1573.81MB Heap size: 3490.71MB +2024-07-09T12:07:24.913324Z | Info | Live bytes: 1573.81MB Heap size: 3490.71MB +2024-07-09T12:08:24.969986Z | Info | Live bytes: 1573.81MB Heap size: 3490.71MB +2024-07-09T12:08:54.867654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:08:55.617662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:08:58.493361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:08:58.967490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:08:59.774871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:14.690154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:22.642312Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:23.116556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:24.973353Z | Info | Live bytes: 1596.33MB Heap size: 3490.71MB +2024-07-09T12:09:28.977605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:31.479163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:32.467927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:34.462721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:34.621054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:35.040128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:40.433698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:40.570376Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:40.625008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:40.678509Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:40.693053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:40.717619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.099970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.172009Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.238583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.365256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:41.367946Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.595500Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.723425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.790210Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:41.938699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:42.131244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:42.800500Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:09:43.487756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:49.376191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:49.469650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:50.185238Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:50.554863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:50.654088Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:50.671193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:50.731595Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:51.206864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:51.228367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:51.485896Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:51.834048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:51.979597Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:51.985840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:52.186736Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:52.293485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:09:52.638456Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:09:52.807666Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:10:25.006458Z | Info | Live bytes: 1703.36MB Heap size: 3559.92MB +2024-07-09T12:11:08.698963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:11:09.883805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:11:13.205666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:11:13.483127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:11:13.792545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:11:14.133718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:11:14.274463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:11:15.494112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:11:15.602437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:11:16.046248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:11:21.253579Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:11:21.359519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:11:25.010212Z | Info | Live bytes: 1743.59MB Heap size: 3621.78MB +2024-07-09T12:12:19.686501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:12:20.276146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:12:20.457757Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:12:25.014344Z | Info | Live bytes: 1747.18MB Heap size: 3636.46MB +2024-07-09T12:12:25.688131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:12:30.798343Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:12:54.260511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:12:54.850467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:12:55.720197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:12:57.529171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:12:57.552757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:12:58.775443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:10.547880Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:10.684383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:10.741178Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:10.761829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:10.812497Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:10.853229Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:11.327678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:11.560124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:11.648542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:11.777237Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:11.872583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:12.013842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:12.061387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:12.115829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:12.236141Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:12.270032Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:12.404822Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:12.628306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:13.639207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:14.222221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:14.380813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:14.550595Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:14.618703Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:14.731653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:14.797170Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:14.908197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:15.102163Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:13:15.782015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:18.571403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:18.580533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:20.507434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:13:25.016278Z | Info | Live bytes: 1882.87MB Heap size: 3757.05MB +2024-07-09T12:13:26.968269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:13:27.448098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:14:25.069330Z | Info | Live bytes: 1896.24MB Heap size: 3757.05MB +2024-07-09T12:15:25.129954Z | Info | Live bytes: 1896.24MB Heap size: 3757.05MB +2024-07-09T12:16:25.186195Z | Info | Live bytes: 1896.24MB Heap size: 3757.05MB +2024-07-09T12:17:19.190484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:17:20.801024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:17:25.191399Z | Info | Live bytes: 1928.39MB Heap size: 3795.85MB +2024-07-09T12:17:34.917714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:17:58.409995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:17:59.192477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:18:05.125581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:18:05.135939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:05.269808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:05.375345Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:05.441544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:05.733535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:05.767669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:18:05.860298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:05.988445Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:06.327427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:18:06.655561Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:18:07.046900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:18:07.409189Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:18:25.209557Z | Info | Live bytes: 1956.08MB Heap size: 3825.21MB +2024-07-09T12:19:17.315691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:19:20.027584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:19:25.211082Z | Info | Live bytes: 1954.13MB Heap size: 3831.50MB +2024-07-09T12:20:25.226483Z | Info | Live bytes: 1960.79MB Heap size: 3831.50MB +2024-07-09T12:20:40.659969Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:40.733028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:41.018609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:42.274929Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:42.409208Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:42.461329Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:42.698654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:44.687278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:46.477689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:47.329718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:47.438977Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:47.635961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:47.776234Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:47.824695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:47.865682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:47.946606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:48.448875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:50.053432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:51.086394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:51.642080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:52.226172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:52.828061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:56.876826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:57.496988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:20:57.570553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:58.234254Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:20:58.921356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:21:25.248919Z | Info | Live bytes: 1034.93MB Heap size: 3980.39MB +2024-07-09T12:22:06.512429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:07.473328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:08.044665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:10.105831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:10.230226Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:10.537284Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:10.596353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:10.748798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:10.856444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:10.914613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:11.249052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:11.747866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:11.851588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:11.978927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:12.019485Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:12.116186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:12.230920Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:12.289883Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:12.610795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:13.259684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:13.853195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:16.054907Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:16.128147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:16.210846Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:16.718826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:17.825175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:18.155970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:22:18.973875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:23.813651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:22:25.252317Z | Info | Live bytes: 1219.97MB Heap size: 3980.39MB +2024-07-09T12:22:30.239880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:23:25.303198Z | Info | Live bytes: 1248.10MB Heap size: 3980.39MB +2024-07-09T12:24:25.335649Z | Info | Live bytes: 1248.10MB Heap size: 3980.39MB +2024-07-09T12:25:14.117935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:14.632838Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:14.710014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:14.798924Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:14.964019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:17.337405Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:17.441377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:17.531940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:17.679280Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:17.976531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:18.041381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:18.123552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:18.228257Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:18.639521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:18.676548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:18.940910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:19.125865Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:19.446175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:20.138222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:20.774312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:21.481878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:25.016866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:25.337186Z | Info | Live bytes: 1303.11MB Heap size: 3980.39MB +2024-07-09T12:25:28.282511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:29.613383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:33.232527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:44.883288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:44.980599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:45.179699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:45.303678Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:45.552281Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:45.623317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:45.763574Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:45.807791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:45.852873Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:46.084648Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:46.190963Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:25:46.371339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:47.064448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:48.119793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:53.447772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:25:56.713579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:04.180925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:06.435992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:07.300592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:13.077856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:13.685632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:25.345363Z | Info | Live bytes: 1340.12MB Heap size: 3980.39MB +2024-07-09T12:26:44.481531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:44.596778Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:44.833280Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:44.935930Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:45.011832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:45.096642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:45.118275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:45.389380Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:45.898095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:45.906202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:46.031186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:46.136216Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:46.193955Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:46.256198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:46.327055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:46.534740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:47.292702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:47.811158Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:47.857046Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:47.906953Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:47.991727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:26:48.163493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:26:48.174808Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:27:25.378505Z | Info | Live bytes: 1381.97MB Heap size: 3980.39MB +2024-07-09T12:28:25.439419Z | Info | Live bytes: 1381.97MB Heap size: 3980.39MB +2024-07-09T12:29:25.489229Z | Info | Live bytes: 1378.74MB Heap size: 3980.39MB +2024-07-09T12:30:24.222017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:24.925471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:25.490563Z | Info | Live bytes: 1393.65MB Heap size: 3980.39MB +2024-07-09T12:30:25.800822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:34.882651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:30:35.327628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:35.810624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:30:35.927860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:36.581573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:37.493781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:38.309762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:38.782008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:30:39.231195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:39.863316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:41.783830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:42.425001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:42.982629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:46.186654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:47.184492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:47.743799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:54.758961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:57.353307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:30:59.017987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:03.806808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:05.084413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:06.166357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:31:06.477999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:08.546950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:09.697404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:12.310527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:13.160227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:14.025069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:15.982697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:20.690661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:25.496319Z | Info | Live bytes: 1433.08MB Heap size: 3980.39MB +2024-07-09T12:31:35.743092Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:31:36.102228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:36.611763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:31:36.749563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:31:36.842853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:36.909457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:31:37.413464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:38.381146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:39.110762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:39.718145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:46.734014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:31:47.232078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:48.326009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:31:52.011425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:00.651701Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:03.615894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:07.095903Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:32:07.202333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:07.780861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:10.427911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:11.511021Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:32:12.237700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:14.030851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:14.756574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:15.049478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:32:15.224447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:32:15.334063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:16.043902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:25.501131Z | Info | Live bytes: 1693.69MB Heap size: 3980.39MB +2024-07-09T12:32:51.889872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:32:52.577598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:33:12.668037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:33:15.856616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:33:16.129419Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:33:25.511521Z | Info | Live bytes: 1712.15MB Heap size: 3980.39MB +2024-07-09T12:34:25.543536Z | Info | Live bytes: 1712.15MB Heap size: 3980.39MB +2024-07-09T12:35:25.545489Z | Info | Live bytes: 1712.15MB Heap size: 3980.39MB +2024-07-09T12:36:25.549014Z | Info | Live bytes: 1712.15MB Heap size: 3980.39MB +2024-07-09T12:36:59.917803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:00.618952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:03.021176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:03.567741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:03.661254Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:03.667156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:03.730946Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:04.236041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:05.134899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:08.744817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:09.181391Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:09.240433Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:09.400315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:09.461747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:09.668996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:09.681800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:10.224066Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:10.320587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:10.407952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:10.662542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:10.723797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:10.882180Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:10.937631Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:11.031413Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:11.384551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:12.592884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:13.232495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:13.704558Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:13.719759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:13.799826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:13.883327Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:13.941671Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:14.296694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:16.297352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:25.554294Z | Info | Live bytes: 1814.86MB Heap size: 3980.39MB +2024-07-09T12:37:31.171552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:31.724585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:34.760533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:38.748013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:38.876094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:39.204852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:39.306633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:39.806377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:39.895262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:40.399307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:43.587694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:47.097746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:47.195962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:47.383851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:47.425784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:47.463716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:47.533766Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:47.672410Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:47.893410Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:48.034630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:48.795787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:56.095550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:56.692262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:56.765964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:56.952345Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:57.068528Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:57.189347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:57.236052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:57.388630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:57.653960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:57.744228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:57.882632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:58.003085Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:58.208124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:58.325675Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:58.457060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:58.497609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:37:59.632018Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:59.817612Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:37:59.848706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:00.016138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:00.096835Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:00.244738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:00.516747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:00.517736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:03.115308Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:03.191422Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:03.316677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:03.579242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:04.373148Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:04.522486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:04.722521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:04.863880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:05.018439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:05.165864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:05.515209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:06.236570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:07.095755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:25.557250Z | Info | Live bytes: 1994.11MB Heap size: 3980.39MB +2024-07-09T12:38:29.169856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:29.816093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:30.454519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:33.595135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:34.335357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:35.015847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:35.816658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:37.019421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:37.624016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:37.780816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:37.854886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:37.976709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:38.733603Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:38.818051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:38.843232Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:38.937812Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:39.234797Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:39.349016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:38:39.450800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:40.149930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:40.890093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:41.455076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:42.176016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:42.890939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:43.439847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:44.198950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:44.832401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:38:45.449685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:03.970700Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:04.043841Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:04.138956Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:04.365684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:04.567951Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:04.649728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:04.755408Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:04.872447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:04.924603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:05.520632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:06.797784Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:06.941498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:07.276438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:07.495941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:08.421877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:10.706430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:18.886967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:19.000581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:19.133729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:19.344689Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:19.397199Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:19.833764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:21.725851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:21.887370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:21.973983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:21.992467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:22.037374Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:22.540640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:25.450852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:25.542302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:25.558182Z | Info | Live bytes: 1203.36MB Heap size: 4073.72MB +2024-07-09T12:39:25.612678Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:25.653561Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:25.752874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:28.222219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.287022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.335624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:28.357473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.417308Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.657939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.703096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.768792Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.854721Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:28.919446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:29.479301Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:29.549775Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:29.668499Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:29.983515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:31.068048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:31.309990Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:31.373204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:39:31.660947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:32.399817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:34.171623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:45.974518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:46.995008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:50.068869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:53.323637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:53.922324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:39:55.363194Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:39:56.041187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:40:03.130757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:40:03.686152Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:40:04.362704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:40:25.580467Z | Info | Live bytes: 1258.56MB Heap size: 4073.72MB +2024-07-09T12:41:02.721567Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:03.183688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:04.339529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:05.791067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:07.339083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:07.815634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:07.826665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:08.318963Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:08.457514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:08.481587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:08.600242Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:08.650189Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:08.747995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:08.932468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:09.093439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:09.329274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:09.410845Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:09.572376Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:09.798859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:10.183939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:10.255544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:10.592295Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:10.675212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:10.709783Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:10.762535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:10.892383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:11.012147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:41:11.269765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:14.319009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:14.988337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:15.642690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:19.641292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:20.285606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:21.073424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:21.925798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:23.314787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:41:25.543356Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:41:25.583309Z | Info | Live bytes: 1402.75MB Heap size: 4073.72MB +2024-07-09T12:41:26.275482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:42:25.611848Z | Info | Live bytes: 1392.51MB Heap size: 4073.72MB +2024-07-09T12:43:25.672265Z | Info | Live bytes: 1392.51MB Heap size: 4073.72MB +2024-07-09T12:44:25.732483Z | Info | Live bytes: 1392.51MB Heap size: 4073.72MB +2024-07-09T12:45:25.756034Z | Info | Live bytes: 1392.51MB Heap size: 4073.72MB +2024-07-09T12:45:41.595710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:42.986684Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:43.091990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:43.094275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:43.151283Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:43.247708Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:43.667280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:44.579916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:45.458373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:45.763480Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:46.101286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:46.414501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:46.592377Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:46.921383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:47.585409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:52.126150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:52.899915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:54.921086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:45:55.302826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:45:57.190862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:46:25.780415Z | Info | Live bytes: 1474.75MB Heap size: 4073.72MB +2024-07-09T12:46:34.243015Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:46:38.786000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:46:48.718502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:46:51.039804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:46:52.900343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:46:59.326158Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:46:59.428714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:46:59.484827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:46:59.573117Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:46:59.804085Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:46:59.819147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:00.040218Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:00.549219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:00.596927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:00.707212Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:00.773551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:00.858507Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:01.212784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:01.352456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:01.426792Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:01.526799Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:01.643864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:01.844373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:01.979460Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:02.070821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:02.143766Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:02.478742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:02.674695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:02.748179Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:03.183619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:03.466623Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:03.531503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:03.609357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:03.965424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:04.075821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:04.577451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:05.647914Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:47:06.326941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:08.301860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:08.895458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:09.418577Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:09.558054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:09.911551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:10.264760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:10.534716Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:11.591661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:11.686562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:11.833638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:12.597898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:13.448674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:14.817974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:15.641371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:25.791322Z | Info | Live bytes: 1601.90MB Heap size: 4073.72MB +2024-07-09T12:47:28.299112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:28.441879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:28.645377Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:29.141464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:29.369553Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:29.722515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:29.860873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:30.243755Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:30.403914Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:30.479047Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:30.746162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:32.120641Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:32.244556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:32.287833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:33.075196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:33.256039Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:33.594709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:33.636623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:33.717242Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:33.880115Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:34.204841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:34.396419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:34.561804Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:34.896005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:35.104683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:35.215882Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:35.324986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:35.448232Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:35.597729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:37.246214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:37.352850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:37.624040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:37.749545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:37.757417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:38.018274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:38.082690Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:38.204501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:38.257447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:38.515489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:39.106942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:40.086933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:40.822347Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:40.882150Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:40.933066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:40.964606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:47:42.230287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:42.807878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:43.363873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:46.142440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:48.647865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:50.398667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:56.676031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:58.196295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:47:58.237391Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:47:58.916260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:48:25.810519Z | Info | Live bytes: 1697.38MB Heap size: 4073.72MB +2024-07-09T12:49:25.871387Z | Info | Live bytes: 1697.38MB Heap size: 4073.72MB +2024-07-09T12:50:04.951267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:06.929359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:07.534244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:50:07.657393Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:08.878756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:09.428631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:10.027625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:13.646436Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:50:13.651371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:14.225906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:25.878352Z | Info | Live bytes: 1723.40MB Heap size: 4073.72MB +2024-07-09T12:50:26.404655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:50:26.880943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:27.659485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:28.211506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:29.052293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:29.632220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:35.961826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:38.662330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:41.106529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:44.169546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:53.180883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:53.916381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:55.260630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:55.844357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:56.895630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:50:57.833366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:00.423508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:00.514109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:01.015294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:02.019018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:02.420761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:02.613709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:02.929742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:04.115516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:04.732152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:05.373459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:06.846713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:07.631390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:07.845617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:10.203569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:10.469910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:10.650302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:10.977166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:12.241559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:15.099572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:21.499351Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:21.658904Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:21.738774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:51:21.989052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:25.879661Z | Info | Live bytes: 1790.69MB Heap size: 4073.72MB +2024-07-09T12:51:26.000331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:28.855966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:29.487197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:34.266821Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:51:59.973931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:00.245524Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:00.581834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:00.606836Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:00.725996Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:00.824543Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:00.929335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:00.990421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:01.100628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:01.181685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:01.233420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:01.368472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:01.871804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:02.045235Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:02.240651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:02.551742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:02.598605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:02.734732Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:03.110731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:03.459240Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:03.655085Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:03.846832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:03.945438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:03.965565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:04.022223Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:04.137064Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:04.533394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:16.029881Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:16.154974Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:16.226522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:16.283879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:16.301725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:16.341045Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:16.850662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:16.918567Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:52:17.598953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:25.888348Z | Info | Live bytes: 1920.39MB Heap size: 4075.81MB +2024-07-09T12:52:26.633087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:29.820097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:32.484017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:33.268041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:37.702337Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:37.860071Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:37.916516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:37.925910Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:38.002273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:38.042920Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:52:38.515384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:39.481286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:40.260024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:40.897383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:41.275588Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:52:41.954507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:45.353663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:49.082492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:49.955116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:52:50.908173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:08.260203Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:08.474291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:08.520498Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:08.591579Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:08.743674Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:09.032507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:09.654941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:10.729905Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:10.976219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:11.040036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:11.197674Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:11.272256Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:11.397130Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:11.485914Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:11.565190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:11.906506Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:53:19.931906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:20.072037Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:20.090213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:20.129594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:20.212890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:20.255419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:20.574537Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:20.627606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:20.641603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:20.692358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:21.014150Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:21.111891Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:21.225988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:21.292149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:21.354965Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:21.791008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:21.821975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:21.952144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:22.021775Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:22.344880Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:53:22.489183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:25.891827Z | Info | Live bytes: 1194.07MB Heap size: 4249.88MB +2024-07-09T12:53:30.469325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:31.109849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:32.220560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:32.920181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:33.520078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:34.001985Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:53:34.684432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:40.940366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:41.593473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:42.247804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:42.811147Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:42.916753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:42.947445Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:43.588147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:45.355896Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:45.735733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:46.703122Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:47.021267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:47.060494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:47.197547Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:53:47.684949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:50.197914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:52.853360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:53:54.892216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:25.899687Z | Info | Live bytes: 1379.56MB Heap size: 4249.88MB +2024-07-09T12:54:28.236222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:32.066421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:32.705279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:33.432455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:36.821723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:37.490735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:38.163851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:39.656530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:41.461806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:44.367993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:44.959424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:45.448491Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:45.532753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:46.615803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:47.488772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:48.206875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:49.098844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:49.122821Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:50.209416Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:50.302604Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:50.702821Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:55.665135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:56.941470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:58.993222Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:59.099004Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:59.273180Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:59.319403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:59.339871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:54:59.441794Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:59.760370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:59.856544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:54:59.941013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:00.011792Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:00.516286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:02.522788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:02.628760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:02.756902Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:02.825759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:02.841115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:02.902542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:03.009236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:03.405484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:04.609183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:08.429792Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:08.479896Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:08.562418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:08.672046Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:09.162817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:10.585250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:10.659465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:10.719893Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:11.028264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:11.066942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:11.211523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:11.293662Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:11.368594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:11.706298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:18.783359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:20.161523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:21.201986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:22.958671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:24.666057Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:24.939465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:25.107038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:25.263162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:25.355391Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:25.425381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:25.503335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:25.581472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:25.900410Z | Info | Live bytes: 1628.97MB Heap size: 4249.88MB +2024-07-09T12:55:27.126157Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:27.304741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:27.334119Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:27.398546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:27.485419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:27.544590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:27.619581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:27.900153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:28.163673Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:55:28.847157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:37.689912Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:37.756642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:37.847553Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:37.908379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:55:37.951191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:52.746533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:54.064412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:55:56.277083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:01.582512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:02.907151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:03.823663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:16.481381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:17.717740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:19.578209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:20.554811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:23.522358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:23.575160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:23.706368Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:24.011029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:25.903540Z | Info | Live bytes: 1850.10MB Heap size: 4249.88MB +2024-07-09T12:56:26.087653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:26.137802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:26.532168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:51.741822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:52.337039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:53.407715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:53.411341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:54.008511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:55.114902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:56.046523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:56.324425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:56.428057Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:56.811108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:56.989731Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:57.494778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:58.279511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:56:58.570728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:58.626028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:58.687334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T12:56:58.986186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:16.486360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:17.109065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:18.878360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:19.219465Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T12:57:25.905579Z | Info | Live bytes: 1939.78MB Heap size: 4249.88MB +2024-07-09T12:57:39.335961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:39.944562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:40.525745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:41.087740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:44.123289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:44.721423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:45.494786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:46.317834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:46.984512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:51.017437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:51.669551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:52.337475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:53.461871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:54.097337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:54.682092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:57:55.343507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T12:58:25.931328Z | Info | Live bytes: 2035.13MB Heap size: 4249.88MB +2024-07-09T12:59:25.983191Z | Info | Live bytes: 2049.58MB Heap size: 4249.88MB +2024-07-09T13:00:25.986304Z | Info | Live bytes: 2049.58MB Heap size: 4249.88MB +2024-07-09T13:01:26.046978Z | Info | Live bytes: 2049.58MB Heap size: 4249.88MB +2024-07-09T13:02:14.884227Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:02:15.562843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:02:26.059552Z | Info | Live bytes: 2056.13MB Heap size: 4249.88MB +2024-07-09T13:03:26.113392Z | Info | Live bytes: 2046.97MB Heap size: 4249.88MB +2024-07-09T13:04:26.174511Z | Info | Live bytes: 2046.97MB Heap size: 4249.88MB +2024-07-09T13:05:26.208749Z | Info | Live bytes: 2046.97MB Heap size: 4249.88MB +2024-07-09T13:06:26.269861Z | Info | Live bytes: 2046.97MB Heap size: 4249.88MB +2024-07-09T13:06:54.009360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:06:55.079992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:55.151711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:06:56.223049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:06:57.120128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:57.368251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:06:57.782664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:57.919821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:58.022204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:58.130186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:58.194015Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:58.257992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:58.283918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:06:58.586275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:58.811275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:58.968211Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:59.100872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:06:59.164994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:06:59.679116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:07:00.264025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:07:03.574136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:07:06.151026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:07:06.877568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:07:11.344708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:07:12.259556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:07:26.279397Z | Info | Live bytes: 2118.02MB Heap size: 4348.44MB +2024-07-09T13:08:26.323149Z | Info | Live bytes: 2118.02MB Heap size: 4348.44MB +2024-07-09T13:09:01.574456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:01.663321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:02.126377Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:02.200594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:02.618006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:25.965061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.109535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.176284Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.209889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:26.271616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.324397Z | Info | Live bytes: 2136.23MB Heap size: 4370.46MB +2024-07-09T13:09:26.490934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.624008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.722900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.772532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:26.826713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:26.974078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:27.047826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:27.185762Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:27.255997Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:27.340401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:27.350584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:27.967200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:28.041923Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:28.556281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:28.891752Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:28.994516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:29.094220Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:29.191295Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:29.250209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:29.415763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:30.930005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:31.327548Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:09:32.007009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:35.458084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:35.540266Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:35.726908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:35.811803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:35.907465Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:35.976135Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:09:35.976577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:36.235164Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:09:47.677912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:53.054954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:09:55.361431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:10.669892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:26.335462Z | Info | Live bytes: 1254.62MB Heap size: 4417.65MB +2024-07-09T13:10:26.726274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:26.879186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:26.956541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:26.972481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:27.013187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:27.390425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:27.460779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:27.529462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:27.571986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:27.676325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:27.844412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:27.928264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:28.052044Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:28.084319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:28.396049Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:28.544198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:28.911804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:30.133248Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:30.158489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:30.448960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:30.598964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:30.700134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:30.741670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:30.839250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:30.942536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:10:31.367378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:31.448052Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:10:32.126426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:45.270645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:45.962034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:50.075905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:10:50.410683Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:11:11.036681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:11.876962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:11.909616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:12.545725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:12.685383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:12.962317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:13.349619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:13.794458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:14.180152Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:14.460314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:14.615869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:15.267022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:15.848439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:19.109337Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:19.572931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:20.525021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:26.336623Z | Info | Live bytes: 1541.81MB Heap size: 4417.65MB +2024-07-09T13:11:26.517844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:27.247086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:29.472192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:30.851134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:31.610360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:31.948205Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:32.228848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:33.411496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:11:34.504043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:35.237547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:39.451327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:49.266152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:55.087871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:11:55.519426Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:11:56.198779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:12:24.739201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:12:26.339275Z | Info | Live bytes: 1688.52MB Heap size: 4417.65MB +2024-07-09T13:12:26.781247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:12:27.027259Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:12:44.852872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:12:44.919958Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:12:48.235369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:12:48.837931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:12:49.883430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:12:50.384920Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:12:51.013760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:13:26.355253Z | Info | Live bytes: 1767.30MB Heap size: 4417.65MB +2024-07-09T13:14:06.706959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:06.833331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:06.946139Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:07.121078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:07.179071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:07.231007Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:07.350681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:07.796897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:07.847341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:07.960138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:08.012817Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:08.413334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:09.180767Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:09.341656Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:09.453777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:14:09.687287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:12.885051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:16.556565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:19.131001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:19.686270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:20.438038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:21.461636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:14:26.361017Z | Info | Live bytes: 1830.46MB Heap size: 4417.65MB +2024-07-09T13:15:26.422001Z | Info | Live bytes: 1830.46MB Heap size: 4417.65MB +2024-07-09T13:15:46.621876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:15:48.505321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:26.205693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:26.205727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:26.280893Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:26.422635Z | Info | Live bytes: 1844.36MB Heap size: 4417.65MB +2024-07-09T13:16:26.664880Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:26.779623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:27.376828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:28.418477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:28.492736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:29.205619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:29.850075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:35.337693Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:16:50.772858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:51.247689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:51.376413Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:51.641270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:51.796073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:51.885760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:51.916049Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:52.124918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:52.217417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:52.615742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:52.628029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:52.683186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:52.799582Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:53.179881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:16:53.642313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:53.749866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:53.823779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:53.875972Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:16:54.126686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:01.969570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:14.311079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:18.951428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:19.109533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:19.206051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:19.335519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:19.399182Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:19.442562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:19.497758Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:20.000607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:20.000757Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:20.425993Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:20.583749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:20.681109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:17:20.912499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:26.423970Z | Info | Live bytes: 1926.34MB Heap size: 4417.65MB +2024-07-09T13:17:26.560920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:27.335420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:28.041786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:28.720385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:29.701486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:30.254593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:30.931762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:31.488304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:32.841858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:17:43.754951Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T13:18:26.466388Z | Info | Live bytes: 1980.53MB Heap size: 4417.65MB +2024-07-09T13:18:32.489923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:19:26.503333Z | Info | Live bytes: 1976.33MB Heap size: 4417.65MB +2024-07-09T13:46:40.199810Z | Info | Live bytes: 1976.33MB Heap size: 4417.65MB +2024-07-09T13:47:40.244563Z | Info | Live bytes: 1976.33MB Heap size: 4417.65MB +2024-07-09T13:48:40.305648Z | Info | Live bytes: 1976.33MB Heap size: 4417.65MB +2024-07-09T13:49:19.879874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:49:22.279984Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T13:49:23.539588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:49:23.569762Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T13:49:25.107643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:49:40.322942Z | Info | Live bytes: 1993.85MB Heap size: 4417.65MB +2024-07-09T13:49:41.324996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:49:45.978720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:50:30.276085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:50:40.329207Z | Info | Live bytes: 2022.66MB Heap size: 4417.65MB +2024-07-09T13:51:40.330376Z | Info | Live bytes: 2022.66MB Heap size: 4417.65MB +2024-07-09T13:52:40.391114Z | Info | Live bytes: 2022.66MB Heap size: 4417.65MB +2024-07-09T13:52:44.926447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:52:46.526493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:53:40.445309Z | Info | Live bytes: 2030.25MB Heap size: 4417.65MB +2024-07-09T13:54:40.457914Z | Info | Live bytes: 2030.25MB Heap size: 4417.65MB +2024-07-09T13:55:04.121420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:55:37.473063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:55:39.788369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:55:40.481328Z | Info | Live bytes: 2030.25MB Heap size: 4417.65MB +2024-07-09T13:55:40.851997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:55:41.496896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:55:45.103252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:55:52.539865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:55:53.609635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:56:40.523182Z | Info | Live bytes: 2044.31MB Heap size: 4417.65MB +2024-07-09T13:56:41.345045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:56:41.475511Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T13:57:17.105917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:18.628852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:21.499152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:21.891311Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:22.094066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:22.678235Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T13:57:25.852361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.040392Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.075136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:26.096189Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.219855Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.598834Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.694081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:26.694148Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.743168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.816982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:26.888455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:27.106850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:27.269773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:27.291749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:27.327467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:27.391568Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T13:57:27.824300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:27.937417Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T13:57:28.662379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:57:40.535312Z | Info | Live bytes: 2103.04MB Heap size: 4417.65MB +2024-07-09T13:58:40.577319Z | Info | Live bytes: 2103.04MB Heap size: 4417.65MB +2024-07-09T13:59:25.355626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:59:26.405400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:59:38.565073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T13:59:40.579191Z | Info | Live bytes: 2109.98MB Heap size: 4417.65MB +2024-07-09T13:59:42.924011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:00:05.889059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:00:07.422037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:00:07.440259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:00:31.575521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:00:40.614880Z | Info | Live bytes: 2115.96MB Heap size: 4417.65MB +2024-07-09T14:01:31.734326Z | Error | Got EOF +2024-07-09 14:04:46.0160000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-09 14:04:46.0170000 [client] INFO Finding haskell-language-server +2024-07-09 14:04:46.0200000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:46.0200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:46.0290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-09 14:04:46.5620000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:46.5620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:46.5740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-09 14:04:46.8920000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:46.8920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:46.9030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-09 14:04:47.2120000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:47.2120000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:47.2200000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-09 14:04:47.4730000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:47.4730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:47.4790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-09 14:04:47.4940000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:47.4940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:47.4990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-09 14:04:47.5280000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:47.5280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:47.5340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-09 14:04:47.5560000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-09 14:04:47.6770000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:47.6770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:47.6840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-09 14:04:47.9540000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-09 14:04:47.9540000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-09 14:04:58.8490000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-09 14:04:58.9160000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-09 14:04:58.9160000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:58.9160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:58.9260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-09 14:04:59.1140000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:59.1140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:59.1210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-09 14:04:59.1410000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:59.1410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:59.1490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-09 14:04:59.1650000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:59.1650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:59.1730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-09 14:04:59.1900000 [client] INFO Checking for ghcup installation +2024-07-09 14:04:59.1900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 14:04:59.1970000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-09 14:04:59.4380000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-09 14:04:59.4390000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-09 14:04:59.4400000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-09 14:04:59.4400000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-09 14:04:59.4400000 [client] INFO server environment variables: +2024-07-09 14:04:59.4400000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-09 14:04:59.4400000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-09 14:04:59.4400000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-09 14:04:59.4430000 [client] INFO Starting language server +2024-07-09T14:05:14.687096Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-09T14:05:14.690684Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-09T14:05:14.691293Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-09T14:05:14.698480Z | Info | Logging heap statistics every 60.00s +2024-07-09T14:05:14.718402Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-09T14:05:14.719409Z | Info | Starting server +2024-07-09T14:05:14.744620Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-09T14:05:14.884994Z | Info | Started LSP server in 0.17s +2024-07-09T14:05:17.019190Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-09T14:05:17.020522Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-09T14:05:17.595113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:05:17.595370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:05:19.251711Z | Info | Load cabal cradle using single file +2024-07-09T14:05:20.593282Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT6996-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-09T14:05:26.445671Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-1615d6206a80f4a0e31ef63d6e69b655fd28231c +2024-07-09T14:05:26.459047Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-09T14:06:14.745265Z | Info | Live bytes: 388.04MB Heap size: 1675.62MB +2024-07-09T14:07:14.756731Z | Info | Live bytes: 388.04MB Heap size: 1675.62MB +2024-07-09T14:08:14.811563Z | Info | Live bytes: 388.04MB Heap size: 1675.62MB +2024-07-09T14:09:14.834556Z | Info | Live bytes: 392.33MB Heap size: 1675.62MB +2024-07-09T14:10:14.842836Z | Info | Live bytes: 402.63MB Heap size: 1675.62MB +2024-07-09T14:10:52.957511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:11:14.844496Z | Info | Live bytes: 418.02MB Heap size: 1675.62MB +2024-07-09T14:11:56.019028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:11:58.207658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:12:01.741476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:12:14.852577Z | Info | Live bytes: 418.23MB Heap size: 1675.62MB +2024-07-09T14:12:36.076157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:12:59.485743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:13:01.756183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:13:01.799833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T14:13:14.872345Z | Info | Live bytes: 512.70MB Heap size: 2041.58MB +2024-07-09T14:14:14.883487Z | Info | Live bytes: 640.82MB Heap size: 2041.58MB +2024-07-09T14:15:14.943674Z | Info | Live bytes: 640.82MB Heap size: 2041.58MB +2024-07-09T14:16:15.004464Z | Info | Live bytes: 640.82MB Heap size: 2041.58MB +2024-07-09T14:17:15.064479Z | Info | Live bytes: 652.12MB Heap size: 2041.58MB +2024-07-09T14:18:15.124566Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:19:15.139958Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:20:15.200520Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:21:15.247754Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:22:15.293480Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:23:15.353473Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:24:15.413568Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:25:15.473683Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:26:15.534536Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:27:15.594509Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:28:15.654570Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:29:15.714490Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:30:15.775025Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:31:15.835438Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:32:15.895524Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:33:15.954146Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:34:16.014565Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:35:16.074501Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:36:16.134477Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:37:16.189071Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:38:16.244539Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:39:16.304559Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:40:16.364427Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:41:16.382577Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:42:16.442615Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:43:16.503446Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:44:16.558111Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:45:16.620185Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:46:16.681875Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:47:16.743581Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:48:16.768804Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:49:16.830048Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:50:16.891217Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:51:16.897847Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:52:16.959145Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:53:17.020534Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:54:17.081493Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:55:17.103046Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:56:17.108172Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:57:17.168808Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:58:17.171025Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T14:59:17.212436Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:00:17.266492Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:01:17.310546Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:02:17.371365Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:03:17.432093Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:04:17.481570Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:05:17.542793Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:06:17.603896Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:07:17.664840Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:08:17.726069Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:09:17.786570Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:10:17.846908Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:11:17.856507Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:12:17.917202Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:13:17.963491Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:14:17.978287Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:15:18.039512Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:16:18.081820Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:17:18.096517Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:18:18.103190Z | Info | Live bytes: 661.61MB Heap size: 2041.58MB +2024-07-09T15:18:23.674688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:18:24.481987Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T15:18:25.346513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:18:34.301417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:18:46.914273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:18:47.318501Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T15:18:54.227831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:01.254747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:12.314068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:13.168335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:18.110566Z | Info | Live bytes: 682.01MB Heap size: 2041.58MB +2024-07-09T15:19:25.604741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:33.986453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:34.911005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:34.988507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:35.182238Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:35.340217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:35.689501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:36.403958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:37.281006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:37.915594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:38.666547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:39.271766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:42.450724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:42.483612Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:42.571664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:42.762567Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:43.075562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:45.142990Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:45.171989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:45.204315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:45.351763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:45.860148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:47.575819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:48.331857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:49.897009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:50.485299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:51.165363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:51.337593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:51.707722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:19:52.226057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:54.696808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:56.299182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:19:56.878011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:20:18.120051Z | Info | Live bytes: 732.93MB Heap size: 2092.96MB +2024-07-09T15:21:18.153757Z | Info | Live bytes: 732.93MB Heap size: 2092.96MB +2024-07-09T15:22:18.214682Z | Info | Live bytes: 732.93MB Heap size: 2092.96MB +2024-07-09T15:22:35.950412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:36.641630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:40.796666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:41.464828Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:41.573007Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:41.674023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:41.760440Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:41.828709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:41.836965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:41.920348Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:42.001187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:42.432951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:43.056205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:44.046368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:45.304436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:45.927766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:46.949495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:48.016277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:49.002119Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:49.113253Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:49.267653Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:49.495148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:50.125816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:50.744459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:51.744111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:51.838343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:52.077191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:53.299139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:54.716793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:55.576384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:56.718028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:57.025083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:22:57.295441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:57.984662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:22:59.785527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:00.040533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:23:00.141651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:23:00.361414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:00.924952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:01.514935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:02.366072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:02.935056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:02.974967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:23:03.688810Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:23:03.760754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:04.765476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:05.381033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:06.159757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:07.354869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:18.222215Z | Info | Live bytes: 760.01MB Heap size: 2184.18MB +2024-07-09T15:23:36.775714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:37.211809Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T15:23:37.912734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:40.721231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:43.373377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:46.745688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:47.853850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:56.272744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:56.908047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:58.220035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:23:59.077676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:06.148837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:06.656720Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T15:24:06.862882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:13.616112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:14.758546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:14.800864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:18.228696Z | Info | Live bytes: 878.50MB Heap size: 2217.74MB +2024-07-09T15:24:22.293292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:22.973789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:23.567951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:24.723383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:25.372506Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:24:25.425228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:35.259875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:48.279241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:24:48.326968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:24:48.398861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:24:48.571863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:49.602715Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:51.085439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:51.890701Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:24:52.452192Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T15:24:56.883474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:25:04.550742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:25:13.726180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:25:18.234487Z | Info | Live bytes: 771.52MB Heap size: 2518.68MB +2024-07-09T15:25:21.495843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:25:21.866844Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T15:25:56.777195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:25:58.301621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:26:15.882785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:26:16.721858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:26:18.236804Z | Info | Live bytes: 825.95MB Heap size: 2518.68MB +2024-07-09T15:26:50.609787Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:26:50.642747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:26:50.684827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:26:50.824733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:26:51.339115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:26:51.951036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:26:52.614077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:27:18.262220Z | Info | Live bytes: 860.86MB Heap size: 2518.68MB +2024-07-09T15:28:18.273587Z | Info | Live bytes: 860.86MB Heap size: 2518.68MB +2024-07-09T15:29:01.263019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:02.213565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:02.847485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:03.422449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:04.103159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:06.473469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:07.127631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:08.191578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:29:08.280749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T15:29:08.302329Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:13.798823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:15.644527Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T15:29:18.276529Z | Info | Live bytes: 956.65MB Heap size: 2518.68MB +2024-07-09T15:29:32.372233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:33.114238Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T15:29:45.118908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:29:48.143962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:30:10.619389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:30:15.898901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T15:30:18.278117Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:31:18.334448Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:32:18.394469Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:33:18.438469Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:34:18.499135Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:35:18.559617Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:36:18.619567Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:37:18.679552Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:38:18.721557Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:39:18.781636Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:40:18.841504Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:41:18.852605Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:42:18.865887Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:43:18.915178Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:44:18.975422Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:45:19.035980Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:46:19.096811Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:47:19.156452Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:48:19.161470Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:49:19.221486Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:50:19.281535Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:51:19.342248Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:52:19.402513Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:53:19.462501Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:54:19.473787Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:55:19.534590Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:56:19.594528Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:57:19.654497Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:58:19.714546Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T15:59:19.774461Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:00:19.834465Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:01:19.871303Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:02:19.931585Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:03:19.967676Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:04:20.027432Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:05:20.085094Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:06:20.145580Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:07:20.205483Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:08:20.265512Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:09:20.325572Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:10:20.386474Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:11:20.403968Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:12:20.424029Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:13:20.458265Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:14:20.507419Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:15:20.551305Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:16:20.611531Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:17:20.671450Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:18:20.731477Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:19:20.791540Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:20:20.841450Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:21:20.850585Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:22:20.910747Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:23:20.971344Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:24:21.031962Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:25:21.092522Z | Info | Live bytes: 1002.30MB Heap size: 2518.68MB +2024-07-09T16:25:41.541953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:25:46.614427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:26:04.472109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:26:06.740227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:26:21.102912Z | Info | Live bytes: 1014.92MB Heap size: 2518.68MB +2024-07-09T16:26:58.199590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:00.406546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:01.135473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:02.184892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:21.104659Z | Info | Live bytes: 1042.40MB Heap size: 2518.68MB +2024-07-09T16:27:29.339364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:30.111242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:30.699096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:53.028468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:27:54.290960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:09.288139Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T16:28:21.117970Z | Info | Live bytes: 1079.34MB Heap size: 2557.48MB +2024-07-09T16:28:30.150861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:30.976560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:32.958577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:33.563951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:34.207098Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:34.223480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:34.854819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:35.417453Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:35.545085Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:35.720324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:35.745428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:35.826274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:36.040232Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:36.310636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:36.323333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:36.636823Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:37.124744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:39.608427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:40.149226Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:40.253265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:40.427806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:40.532728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:40.624808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:40.699188Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:28:41.482395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:48.359400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:28:48.925247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:10.601645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:11.565157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:14.014840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:14.775508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:15.125612Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:29:15.212421Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:29:15.396362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:29:15.561396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:29:15.587713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:15.964276Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:29:16.743060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:18.480288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:19.121325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:20.608022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:21.119233Z | Info | Live bytes: 620.22MB Heap size: 2703.23MB +2024-07-09T16:29:21.277840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:21.869318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:22.630585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:23.320197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:23.979267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:29:24.692868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:30:21.177220Z | Info | Live bytes: 622.97MB Heap size: 2703.23MB +2024-07-09T16:31:21.196477Z | Info | Live bytes: 622.97MB Heap size: 2703.23MB +2024-07-09T16:32:16.401629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:32:21.199132Z | Info | Live bytes: 630.82MB Heap size: 2703.23MB +2024-07-09T16:32:21.426221Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T16:32:21.528466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:33:21.211973Z | Info | Live bytes: 634.49MB Heap size: 2703.23MB +2024-07-09T16:34:21.264793Z | Info | Live bytes: 634.49MB Heap size: 2703.23MB +2024-07-09T16:35:21.270482Z | Info | Live bytes: 634.49MB Heap size: 2703.23MB +2024-07-09T16:35:54.500594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:35:55.100268Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:35:55.187270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:35:55.337456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:35:55.431608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:35:56.136709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:35:56.954947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:05.140651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:12.473363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:13.560695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:36:13.679831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:36:13.776387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:36:14.074734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:14.903491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:15.889845Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs" ] +2024-07-09T16:36:16.502401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:21.272880Z | Info | Live bytes: 900.52MB Heap size: 2703.23MB +2024-07-09T16:36:54.556665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:55.328361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:56.051653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:36:56.768278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:21.294247Z | Info | Live bytes: 1033.37MB Heap size: 2703.23MB +2024-07-09T16:37:34.704433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:42.093654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:44.213905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:44.928633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:50.376569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:52.371459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:53.050920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:55.199081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:56.770220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:37:58.914344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:00.111232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:00.735428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:01.341367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:02.084663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:02.998091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:21.314761Z | Info | Live bytes: 1055.65MB Heap size: 2703.23MB +2024-07-09T16:38:37.481863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:38:37.599669Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:38:37.680512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:37.709058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:38:38.275896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:41.893962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:38:42.363612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:42.405235Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:38:42.541195Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:38:43.030427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:38:43.642870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:39:19.817592Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:19.947782Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:19.965619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:39:20.620364Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:20.827149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:21.093007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:39:21.316470Z | Info | Live bytes: 1087.90MB Heap size: 2703.23MB +2024-07-09T16:39:21.984137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:39:22.261714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:22.400374Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:22.499217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:22.737488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:39:23.429568Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:23.568832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:23.722494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:39:23.913775Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:39:24.548757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:05.228020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:06.208686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:09.185252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:09.425100Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:40:09.694341Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:40:09.810667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:10.534771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:40:10.668973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:10.830865Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:40:11.324419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:13.015762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:13.876977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:15.578696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:21.317528Z | Info | Live bytes: 583.82MB Heap size: 2718.96MB +2024-07-09T16:40:29.568960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:30.397723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:31.330050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:31.940003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:32.619279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:33.324572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:33.890893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:34.463877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:40:34.548807Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T16:41:21.365384Z | Info | Live bytes: 626.70MB Heap size: 2718.96MB +2024-07-09T16:42:21.377113Z | Info | Live bytes: 626.70MB Heap size: 2718.96MB +2024-07-09T16:43:21.438214Z | Info | Live bytes: 626.70MB Heap size: 2718.96MB +2024-07-09T16:44:21.495276Z | Info | Live bytes: 626.70MB Heap size: 2718.96MB +2024-07-09T16:45:21.555464Z | Info | Live bytes: 626.70MB Heap size: 2718.96MB +2024-07-09T16:45:23.757840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:45:24.521381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:45:24.642028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:45:24.787731Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:45:24.954142Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:45:25.042546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:45:25.713529Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T16:45:25.901335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:46:04.103025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:46:07.383355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:46:11.319068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:46:13.059604Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:46:16.689735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:46:21.556360Z | Info | Live bytes: 817.39MB Heap size: 2718.96MB +2024-07-09T16:47:21.593657Z | Info | Live bytes: 817.39MB Heap size: 2718.96MB +2024-07-09T16:48:21.655233Z | Info | Live bytes: 817.39MB Heap size: 2718.96MB +2024-07-09T16:49:21.710699Z | Info | Live bytes: 817.39MB Heap size: 2718.96MB +2024-07-09T16:50:08.836256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:50:09.404396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:50:09.982659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:50:11.284981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:50:21.717587Z | Info | Live bytes: 965.56MB Heap size: 2718.96MB +2024-07-09T16:51:21.778886Z | Info | Live bytes: 972.62MB Heap size: 2718.96MB +2024-07-09T16:51:37.238687Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:37.289083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:37.535407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:37.957768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:38.306570Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:38.453388Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:38.569813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:38.683734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:38.797371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:39.063017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:39.155192Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:39.255535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:39.541717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:44.052579Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:44.139553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:44.870391Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:45.276889Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:45.376394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:45.437829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:48.737523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:48.805276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:48.832937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:49.180812Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:49.697165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:49.738650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:50.082403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:50.206532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:50.294967Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-09T16:51:50.561164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:56.304825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:51:57.851614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:03.220989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:03.952886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:05.605928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:07.311977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:07.974384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:08.665519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:09.298251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:11.416807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:12.065044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:13.939446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:16.569123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:17.224567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:17.884286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:21.783999Z | Info | Live bytes: 1090.15MB Heap size: 2724.20MB +2024-07-09T16:52:23.836284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:24.576323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:26.139295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:28.075651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:30.382583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:31.056582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:52:31.108210Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Scripts/New.hs": [ ] +2024-07-09T16:52:31.816822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-09T16:53:21.808882Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T16:54:21.821744Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T16:55:21.849437Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T16:56:21.909722Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T16:57:21.911069Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T16:58:21.919373Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T16:59:21.925403Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:00:21.985777Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:01:22.047121Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:02:22.094494Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:03:22.100671Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:04:22.104804Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:05:22.165541Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:06:22.225607Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:07:22.286614Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:08:22.346495Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:09:22.406616Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:10:22.467432Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:11:22.527589Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:12:22.587583Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:13:22.614156Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:14:22.674487Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:32:17.847166Z | Info | Live bytes: 580.53MB Heap size: 2772.43MB +2024-07-09T17:32:42.551399Z | Error | Got EOF +2024-07-09 17:36:47.5190000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-09 17:36:47.5210000 [client] INFO Finding haskell-language-server +2024-07-09 17:36:47.5240000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:47.5240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:47.5300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-09 17:36:47.9150000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:47.9150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:47.9210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-09 17:36:48.1610000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:48.1610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:48.1660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-09 17:36:48.3310000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:48.3310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:48.3370000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-09 17:36:48.5490000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:48.5500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:48.5570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-09 17:36:48.5770000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:48.5770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:48.5820000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-09 17:36:48.5970000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:48.5980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:48.6040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-09 17:36:48.6250000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-09 17:36:48.7520000 [client] INFO Checking for ghcup installation +2024-07-09 17:36:48.7530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-09 17:36:48.7580000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-09 17:36:48.9550000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-09 17:36:48.9560000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-10 09:03:42.9320000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-10 09:03:42.9340000 [client] INFO Finding haskell-language-server +2024-07-10 09:03:42.9360000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:42.9360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:42.9450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-10 09:03:43.3010000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:43.3010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:43.3090000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-10 09:03:43.4260000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:43.4260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:43.4310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-10 09:03:43.5770000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:43.5770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:43.5820000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-10 09:03:43.7530000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:43.7530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:43.7610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-10 09:03:43.7870000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:43.7870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:43.7960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-10 09:03:43.8180000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:43.8190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:43.8270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-10 09:03:43.8480000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-10 09:03:43.8950000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:43.8950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:43.9000000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-10 09:03:44.0280000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-10 09:03:44.0290000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-10 09:03:55.1670000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-10 09:03:55.4630000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-10 09:03:55.4640000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:55.4640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:55.4720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-10 09:03:55.6090000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:55.6100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:55.6170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-10 09:03:55.6380000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:55.6390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:55.6460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-10 09:03:55.6630000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:55.6630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:55.6710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-10 09:03:55.6870000 [client] INFO Checking for ghcup installation +2024-07-10 09:03:55.6870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-10 09:03:55.6950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-10 09:03:55.8630000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-10 09:03:55.8640000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-10 09:03:55.8640000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-10 09:03:55.8640000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-10 09:03:55.8640000 [client] INFO server environment variables: +2024-07-10 09:03:55.8650000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-10 09:03:55.8650000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-10 09:03:55.8650000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-10 09:03:55.8670000 [client] INFO Starting language server +2024-07-10T09:04:07.443414Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-10T09:04:07.445426Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-10T09:04:07.449037Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-10T09:04:07.455917Z | Info | Logging heap statistics every 60.00s +2024-07-10T09:04:07.468113Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-10T09:04:07.468785Z | Info | Starting server +2024-07-10T09:04:07.471416Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-10T09:04:07.591052Z | Info | Started LSP server in 0.12s +2024-07-10T09:04:09.276478Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-10T09:04:09.278651Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-10T09:04:09.796717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:04:11.236153Z | Info | Load cabal cradle using single file +2024-07-10T09:04:12.426645Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT117837-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-10T09:04:21.506745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:04:27.813125Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-8.49.0.0-inplace-internal-1615d6206a80f4a0e31ef63d6e69b655fd28231c +2024-07-10T09:04:27.817843Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-8.49.0.0-inplace-internal] +2024-07-10T09:04:42.343084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:04:52.500313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:05:07.472533Z | Info | Live bytes: 824.74MB Heap size: 2044.72MB +2024-07-10T09:05:18.192960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:05:39.651251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:05:43.123333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:06:07.129829Z | Info | LSP: received shutdown +2024-07-10T09:06:07.132506Z | Error | Got EOF +2024-07-10T09:06:37.130805Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-10T09:06:37.131682Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-10T09:06:37.131845Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-10T09:06:37.133889Z | Info | Logging heap statistics every 60.00s +2024-07-10T09:06:37.140607Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-10T09:06:37.141007Z | Info | Starting server +2024-07-10T09:06:37.142448Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-10T09:06:37.191940Z | Info | Started LSP server in 0.05s +2024-07-10T09:06:38.787339Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-10T09:06:38.789165Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-10T09:06:39.297428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-10T09:06:40.921476Z | Info | Load cabal cradle using single file +2024-07-10T09:06:42.064641Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT121439-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-10T09:07:00.833931Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-10T09:07:00.845395Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-10T09:07:37.157361Z | Info | Live bytes: 817.78MB Heap size: 2067.79MB +2024-07-10T09:08:37.211428Z | Info | Live bytes: 817.78MB Heap size: 2067.79MB +2024-07-10T09:09:37.272274Z | Info | Live bytes: 817.78MB Heap size: 2067.79MB +2024-07-10T09:10:37.333602Z | Info | Live bytes: 817.78MB Heap size: 2067.79MB +2024-07-10T09:11:37.394561Z | Info | Live bytes: 817.78MB Heap size: 2067.79MB +2024-07-10T09:12:37.395933Z | Info | Live bytes: 800.15MB Heap size: 2067.79MB +2024-07-10T09:13:37.451895Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:14:37.513014Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:15:37.573746Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:16:37.634347Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:17:37.695044Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:18:37.755910Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:19:37.816449Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:20:37.877298Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:21:37.938412Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:22:37.989453Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:23:38.009632Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:24:38.070876Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:25:38.089130Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:26:38.105773Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:27:38.166936Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:28:38.187577Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:29:38.248800Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:30:38.309477Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:31:38.363565Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:32:38.424821Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:33:38.485974Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:34:38.546803Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:35:38.608049Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:36:38.669099Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:37:38.729679Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:38:38.790489Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:39:38.851504Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:40:38.912919Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:41:38.974557Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:42:39.036353Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:43:39.097737Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:44:39.159519Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:45:39.220892Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:46:39.282477Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:47:39.343961Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:48:39.405393Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:49:39.466837Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:50:39.527664Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:51:39.589066Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:52:39.641772Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:53:39.703301Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:54:39.764713Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:55:39.825821Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:56:39.886519Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:57:39.943919Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:58:39.956494Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T09:59:39.968881Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:00:40.025550Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:01:40.086386Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:02:40.147560Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:03:40.209038Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:04:40.270439Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:05:40.331693Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:06:40.362947Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:07:40.423961Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:08:40.473579Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:09:40.530071Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:10:40.546048Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:11:40.561425Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:12:40.621407Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:13:40.682318Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:14:40.742422Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:15:40.744539Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:16:40.765780Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:17:40.826608Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:18:40.853683Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:19:40.866344Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:20:40.927077Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:21:40.939393Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:22:40.999491Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:23:41.013870Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:24:41.074988Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:25:41.129629Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:26:41.190755Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:27:41.251762Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:28:41.282859Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:29:41.299588Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:30:41.335063Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:31:41.341038Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:32:41.366461Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:33:41.373409Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:34:41.434229Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:35:41.494927Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:36:41.509718Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:37:41.570481Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T10:38:41.631262Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:47:46.889924Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:48:46.920801Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:49:46.982456Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:50:47.043871Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:51:47.105093Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:52:47.165832Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:53:47.172842Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:54:47.233587Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:55:47.253625Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:56:47.313595Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:57:47.374340Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:58:47.399041Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T13:59:47.460642Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:00:47.522186Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:01:47.569712Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:02:47.630657Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:03:47.690565Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:04:47.750588Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:05:47.790558Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:06:47.851231Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:07:47.884671Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:08:47.945839Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:09:47.999896Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:10:48.061464Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:11:48.072688Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:12:48.089220Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:13:48.127815Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:14:48.150986Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:15:48.211952Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:16:48.272673Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:17:48.333375Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:18:48.367728Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:19:48.428627Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:20:48.459630Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:21:48.520651Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:22:48.582014Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:23:48.639719Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:24:48.647736Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:25:48.708824Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:26:48.770437Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:27:48.831835Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:28:48.893295Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:29:48.954675Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:30:48.998941Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:31:49.059598Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:32:49.120709Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:33:49.173169Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:34:49.233822Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:35:49.295514Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:36:49.356898Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:37:49.418219Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:38:49.420118Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:39:49.481817Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:40:49.543274Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:41:49.604803Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:42:49.666248Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:43:49.727573Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:44:49.788906Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T14:45:49.850341Z | Info | Live bytes: 813.17MB Heap size: 2067.79MB +2024-07-10T22:54:35.852367Z | Error | Got EOF +2024-07-11 10:24:16.9650000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-11 10:24:16.9680000 [client] INFO Finding haskell-language-server +2024-07-11 10:24:16.9740000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:16.9740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:16.9850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-11 10:24:17.5750000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:17.5750000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:17.5870000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-11 10:24:17.8330000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:17.8340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:17.8400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-11 10:24:18.1080000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:18.1090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:18.1150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-11 10:24:18.3600000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:18.3610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:18.3690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-11 10:24:18.3850000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:18.3850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:18.3910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-11 10:24:18.4060000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:18.4060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:18.4180000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-11 10:24:18.4840000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-11 10:24:18.5790000 [client] INFO Checking for ghcup installation +2024-07-11 10:24:18.5800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-11 10:24:18.5880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-11 10:24:18.8360000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-11 10:24:18.8370000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-12 17:32:14.3960000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-12 17:32:14.4080000 [client] INFO Finding haskell-language-server +2024-07-12 17:32:14.4100000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:14.4100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:14.4210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-12 17:32:14.7200000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:14.7200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:14.7240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-12 17:32:14.8770000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:14.8780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:14.8900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-12 17:32:15.1020000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:15.1020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:15.1060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-12 17:32:15.2380000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:15.2390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:15.2450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-12 17:32:15.2610000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:15.2610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:15.2700000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-12 17:32:15.2870000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:15.2880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:15.2960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-12 17:32:15.3240000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-12 17:32:15.3920000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:15.3920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:15.4030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-12 17:32:15.5620000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-12 17:32:15.5630000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-12 17:32:17.8220000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-12 17:32:17.8850000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-12 17:32:17.8850000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:17.8850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:17.8910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-12 17:32:17.9850000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:17.9860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:17.9910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-12 17:32:18.0080000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:18.0080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:18.0120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-12 17:32:18.0260000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:18.0260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:18.0300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-12 17:32:18.0450000 [client] INFO Checking for ghcup installation +2024-07-12 17:32:18.0450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-12 17:32:18.0510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-12 17:32:18.2180000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-12 17:32:18.2200000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-12 17:32:18.2200000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-12 17:32:18.2200000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-12 17:32:18.2200000 [client] INFO server environment variables: +2024-07-12 17:32:18.2200000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-12 17:32:18.2210000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-12 17:32:18.2210000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-12 17:32:18.2240000 [client] INFO Starting language server +2024-07-12T17:32:49.929545Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-12T17:32:49.931995Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-12T17:32:49.932434Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-12T17:32:49.938248Z | Info | Logging heap statistics every 60.00s +2024-07-12T17:32:49.951839Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-12T17:32:49.952321Z | Info | Starting server +2024-07-12T17:32:49.974963Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-12T17:32:50.082042Z | Info | Started LSP server in 0.13s +2024-07-12T17:33:49.998238Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:34:50.059263Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:35:50.080448Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:36:50.142224Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:37:50.164216Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:38:50.225514Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:39:50.286428Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:40:50.347378Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:41:50.408242Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:42:50.469083Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:43:50.530249Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-12T17:44:18.089794Z | Error | Got EOF +2024-07-13 17:24:25.2610000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-13 17:24:25.2720000 [client] INFO Finding haskell-language-server +2024-07-13 17:24:25.2730000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:25.2730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:25.2820000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-13 17:24:25.5720000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:25.5720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:25.5790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-13 17:24:25.7610000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:25.7620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:25.7720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-13 17:24:25.9210000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:25.9220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:25.9290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-13 17:24:26.0740000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:26.0750000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:26.0840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-13 17:24:26.1010000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:26.1020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:26.1120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-13 17:24:26.1290000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:26.1290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:26.1390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-13 17:24:26.1710000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-13 17:24:26.2380000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:26.2380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:26.2490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-13 17:24:26.4180000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-13 17:24:26.4180000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-13 17:24:33.6890000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-13 17:24:33.7960000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-13 17:24:33.7960000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:33.7970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:33.8040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-13 17:24:33.9300000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:33.9300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:33.9370000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-13 17:24:33.9560000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:33.9560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:33.9640000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-13 17:24:33.9800000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:33.9810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:33.9890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-13 17:24:34.0050000 [client] INFO Checking for ghcup installation +2024-07-13 17:24:34.0050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-13 17:24:34.0130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-13 17:24:34.1900000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-13 17:24:34.1910000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-13 17:24:34.1910000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-13 17:24:34.1910000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-13 17:24:34.1910000 [client] INFO server environment variables: +2024-07-13 17:24:34.1910000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-13 17:24:34.1910000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-13 17:24:34.1910000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-13 17:24:34.1940000 [client] INFO Starting language server +2024-07-13T17:24:44.570555Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-13T17:24:44.571600Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-13T17:24:44.572028Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-13T17:24:44.574992Z | Info | Logging heap statistics every 60.00s +2024-07-13T17:24:44.581753Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-13T17:24:44.582108Z | Info | Starting server +2024-07-13T17:24:44.583927Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-13T17:24:44.668529Z | Info | Started LSP server in 0.09s +2024-07-13T17:24:46.261766Z | Info | LSP: received shutdown +2024-07-13T17:24:46.263190Z | Info | Reactor thread stopped +2024-07-13T17:24:46.281274Z | Error | Got EOF +2024-07-14 18:22:11.1500000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-14 18:22:11.1520000 [client] INFO Finding haskell-language-server +2024-07-14 18:22:11.1540000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:11.1550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:11.1620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-14 18:22:11.6300000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:11.6300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:11.6390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-14 18:22:11.9560000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:11.9560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:11.9630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-14 18:22:12.2120000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:12.2130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:12.2230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-14 18:22:12.4800000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:12.4800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:12.4890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-14 18:22:12.5070000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:12.5080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:12.5150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-14 18:22:12.5530000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:12.5540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:12.5600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-14 18:22:12.5880000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-14 18:22:12.7660000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:12.7660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:12.7760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-14 18:22:13.0350000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-14 18:22:13.0360000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-14 18:22:23.8870000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-14 18:22:24.0370000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-14 18:22:24.0370000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:24.0380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:24.0440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-14 18:22:24.1590000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:24.1590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:24.1650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-14 18:22:24.1870000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:24.1870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:24.1940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-14 18:22:24.2100000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:24.2100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:24.2170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-14 18:22:24.2340000 [client] INFO Checking for ghcup installation +2024-07-14 18:22:24.2340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 18:22:24.2420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-14 18:22:24.3780000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-14 18:22:24.3790000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-14 18:22:24.3790000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-14 18:22:24.3790000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-14 18:22:24.3790000 [client] INFO server environment variables: +2024-07-14 18:22:24.3790000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-14 18:22:24.3790000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-14 18:22:24.3790000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-14 18:22:24.3800000 [client] INFO Starting language server +2024-07-14T18:22:36.147466Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-14T18:22:36.149212Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-14T18:22:36.149458Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-14T18:22:36.152980Z | Info | Logging heap statistics every 60.00s +2024-07-14T18:22:36.161421Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-14T18:22:36.161826Z | Info | Starting server +2024-07-14T18:22:36.175720Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-14T18:22:36.211860Z | Info | Started LSP server in 0.05s +2024-07-14T18:22:37.609958Z | Info | Cradle path: cardano-api/internal/Cardano/Api/SerialiseTextEnvelope.hs +2024-07-14T18:22:37.610894Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-14T18:22:38.182593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-14T18:22:39.325480Z | Info | Load cabal cradle using single file +2024-07-14T18:22:40.650897Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT31508-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-14T18:22:48.976025Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-c875534007e32f9c29d109be7ba71e4921e24ed2 +2024-07-14T18:22:48.981583Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-14T18:23:36.188564Z | Info | Live bytes: 711.39MB Heap size: 1891.63MB +2024-07-14T18:24:36.248703Z | Info | Live bytes: 711.39MB Heap size: 1891.63MB +2024-07-14T18:25:36.308656Z | Info | Live bytes: 711.39MB Heap size: 1891.63MB +2024-07-14T18:26:36.369218Z | Info | Live bytes: 711.39MB Heap size: 1891.63MB +2024-07-14T18:26:48.640933Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/SerialiseTextEnvelope.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Sign.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Keys/Shelley.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Keys/Class.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Keys/Byron.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Keys/Praos.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/VotingProcedure.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/ProposalProcedure.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/DeserialiseAnyOf.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/SerialiseLedgerCddl.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/OperationalCertificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Keys/Read.hs" ] +2024-07-14T18:26:50.332593Z | Info | Cradle path: cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/Envelope.hs +2024-07-14T18:26:50.333098Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-14T18:26:50.379820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-14T18:26:51.896629Z | Info | Load cabal cradle using single file +2024-07-14T18:26:52.887071Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:test:cardano-api-test + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT31508-183 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-14T18:26:55.030428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-14T18:27:01.439253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-14T18:27:06.466488Z | Info | LSP: received shutdown +2024-07-14T18:27:06.467678Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-07-14T18:27:06.469899Z | Error | Got EOF +2024-07-14T18:27:32.802722Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-14T18:27:32.803888Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-14T18:27:32.804293Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-14T18:27:32.807468Z | Info | Logging heap statistics every 60.00s +2024-07-14T18:27:32.815353Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-14T18:27:32.815851Z | Info | Starting server +2024-07-14T18:27:32.817433Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-14T18:27:32.851988Z | Info | Started LSP server in 0.04s +2024-07-14T18:27:34.254771Z | Info | Cradle path: cardano-api/internal/Cardano/Api/SerialiseTextEnvelope.hs +2024-07-14T18:27:34.256159Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-14T18:27:34.852453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-14T18:27:35.762215Z | Info | Load cabal cradle using single file +2024-07-14T18:27:36.717306Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT39234-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-14T18:27:43.892133Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-14T18:27:43.896178Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-14T18:28:32.852725Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:29:32.873612Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:30:32.934615Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:31:32.957262Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:32:32.991499Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:33:33.052555Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:34:33.064977Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:35:33.088253Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:36:33.118590Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:37:33.119840Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:38:33.121261Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:39:33.122219Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:40:33.127585Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:41:33.139470Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:42:33.200907Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:43:33.261703Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:44:33.322507Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:45:33.353479Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:46:33.371200Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:47:33.377656Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:48:33.409919Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:49:33.444031Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:50:33.505702Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:51:33.567057Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:52:33.569956Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:53:33.624700Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:54:33.669833Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:55:33.703796Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:56:33.761733Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:57:33.821629Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:58:33.882424Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T18:59:33.932497Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:00:33.993300Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:01:34.053710Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:02:34.113595Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:03:34.129789Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:04:34.182300Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:05:34.238788Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:06:34.299732Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:07:34.360817Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:08:34.365609Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:09:34.418007Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:10:34.478947Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:11:34.531430Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:12:34.591692Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:13:34.651779Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:14:34.702811Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:15:34.764166Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:16:34.825548Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:17:34.884979Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:18:34.888777Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:19:34.950198Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:20:35.011565Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:21:35.072622Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:22:35.104718Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:23:35.166066Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:24:35.227491Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:25:35.251548Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:26:35.281676Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:27:35.342544Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:28:35.403287Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:29:35.464963Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:30:35.514858Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:31:35.531483Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:32:35.592731Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:33:35.601498Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:34:35.661533Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:35:35.721586Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:36:35.782443Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:37:35.842766Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:38:35.903774Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:39:35.965076Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:40:36.026378Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:41:36.031552Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:42:36.039775Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:43:36.077640Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:44:36.134574Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:45:36.177869Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:46:36.190495Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:47:36.251557Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:48:36.312713Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:49:36.373751Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:50:36.391495Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:51:36.418147Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:52:36.479459Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:53:36.539688Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:54:36.570415Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:55:36.631362Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:56:36.692671Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:57:36.727448Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:58:36.785473Z | Info | Live bytes: 574.08MB Heap size: 1967.13MB +2024-07-14T19:58:42.875768Z | Info | LSP: received shutdown +2024-07-14T19:58:42.876306Z | Error | Got EOF +2024-07-14 19:59:03.2980000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-14 19:59:03.2990000 [client] INFO Finding haskell-language-server +2024-07-14 19:59:03.3010000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:03.3010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:03.3070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-14 19:59:03.6450000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:03.6450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:03.6510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-14 19:59:03.8010000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:03.8010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:03.8070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-14 19:59:03.9220000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:03.9220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:03.9280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-14 19:59:04.0480000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:04.0490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:04.0530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-14 19:59:04.0670000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:04.0670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:04.0740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-14 19:59:04.0890000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:04.0890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:04.0940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-14 19:59:04.1130000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-14 19:59:04.1590000 [client] INFO Checking for ghcup installation +2024-07-14 19:59:04.1600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-14 19:59:04.1650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-14 19:59:04.2790000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-14 19:59:04.2800000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-15 06:34:19.7850000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-15 06:34:19.7860000 [client] INFO Finding haskell-language-server +2024-07-15 06:34:19.7880000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:19.7880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:19.7950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-15 06:34:20.0050000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:20.0060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:20.0120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-15 06:34:20.2390000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:20.2390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:20.2450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-15 06:34:20.3810000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:20.3810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:20.3860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-15 06:34:20.5270000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:20.5270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:20.5320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-15 06:34:20.5590000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:20.5590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:20.5660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-15 06:34:20.5820000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:20.5830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:20.5890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-15 06:34:20.6120000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-15 06:34:20.6510000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:20.6510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:20.6570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-15 06:34:20.8090000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-15 06:34:20.8100000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-15 06:34:23.4860000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-15 06:34:23.7890000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-15 06:34:23.7890000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:23.7890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:23.7930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-15 06:34:23.8770000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:23.8770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:23.8810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-15 06:34:23.8960000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:23.8960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:23.9000000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-15 06:34:23.9140000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:23.9140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:23.9190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-15 06:34:23.9340000 [client] INFO Checking for ghcup installation +2024-07-15 06:34:23.9340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 06:34:23.9390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-15 06:34:24.0450000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-15 06:34:24.0460000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-15 06:34:24.0460000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-15 06:34:24.0460000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15 06:34:24.0460000 [client] INFO server environment variables: +2024-07-15 06:34:24.0460000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-15 06:34:24.0460000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-15 06:34:24.0460000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-15 06:34:24.0480000 [client] INFO Starting language server +2024-07-15T06:34:34.880123Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-15T06:34:34.882676Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15T06:34:34.883171Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T06:34:34.888880Z | Info | Logging heap statistics every 60.00s +2024-07-15T06:34:34.903440Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T06:34:34.903922Z | Info | Starting server +2024-07-15T06:34:34.922021Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-15T06:34:35.014123Z | Info | Started LSP server in 0.11s +2024-07-15T06:34:36.674822Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Eras/Core.hs +2024-07-15T06:34:36.676831Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-15T06:34:37.089327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T06:34:38.728604Z | Info | Load cabal cradle using single file +2024-07-15T06:34:40.206929Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT8595-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-15T06:34:45.029091Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-15T06:34:45.041479Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-15T06:35:34.937308Z | Info | Live bytes: 238.13MB Heap size: 1389.36MB +2024-07-15T06:36:34.998375Z | Info | Live bytes: 238.13MB Heap size: 1389.36MB +2024-07-15T06:36:38.858568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T06:37:02.590672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T06:37:35.025761Z | Info | Live bytes: 352.73MB Heap size: 1682.96MB +2024-07-15T06:38:09.319457Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T06:38:25.458461Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Core.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Case.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ByronToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Feature.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" ] +2024-07-15T06:38:25.512658Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Core.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Case.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ByronToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Feature.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" ] +2024-07-15T06:38:25.633543Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Core.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Case.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ByronToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Feature.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" ] +2024-07-15T06:38:25.797232Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Core.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Case.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Modes.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ByronToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Feature.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" ] +2024-07-15T06:38:25.849605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T06:38:35.028489Z | Info | Live bytes: 636.81MB Heap size: 2198.86MB +2024-07-15T06:39:25.534604Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T06:39:35.031802Z | Info | Live bytes: 724.84MB Heap size: 2677.01MB +2024-07-15T06:40:35.071119Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:41:35.131083Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:42:35.168211Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:43:35.229135Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:44:35.290150Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:45:16.203770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T06:45:35.294457Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:46:35.344226Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:47:35.376516Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:48:35.386495Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:49:35.447491Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:50:35.508219Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:51:35.568162Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:52:35.628231Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:53:35.688164Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:54:35.709248Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:55:35.770432Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:56:35.802398Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:57:35.864152Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:58:35.925451Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T06:59:35.986391Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:00:36.003361Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:01:36.064282Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:02:36.124210Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:03:36.184628Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:04:36.237116Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:05:36.297083Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:06:36.357754Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:07:36.418264Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:08:36.478185Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:09:36.510498Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:10:36.568339Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:11:36.629913Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:12:36.691502Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:13:36.752921Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:14:36.780951Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:15:36.841575Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:16:36.874381Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:17:36.935681Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:18:36.996208Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:19:37.037267Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:20:37.098537Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:21:37.148589Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:22:37.209818Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:23:37.270151Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:24:37.330330Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:25:37.331697Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:26:37.393108Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:27:37.454443Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:28:37.462099Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:29:37.490425Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:30:37.551844Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:31:37.613283Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:32:37.674056Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:33:37.690349Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:34:37.704190Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:35:37.719502Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:36:37.732754Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:37:37.750544Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:38:37.811167Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:39:37.872268Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:40:37.933358Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:41:37.966419Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:42:38.027154Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:43:38.088009Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:44:38.137619Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:45:38.147120Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:46:38.159346Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:47:38.171089Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:48:38.232022Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:49:38.292172Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:50:38.330677Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:51:38.391951Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:52:38.422351Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:53:38.483849Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:54:38.544994Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:55:38.595262Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:56:38.597886Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:57:38.640921Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:58:38.701895Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T07:59:38.736579Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:00:38.797525Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:01:38.858241Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:02:38.864827Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:03:38.926107Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:04:38.935800Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:05:38.997102Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:06:39.058232Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:07:39.082310Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:08:39.142365Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:09:39.175340Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:10:39.236343Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:11:39.297549Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:12:39.358442Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:13:39.398402Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:14:39.459490Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:15:39.520297Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:16:39.576355Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:17:39.608394Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:18:39.621545Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:19:39.671637Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:20:39.678445Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:21:39.739723Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:22:39.742469Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:23:39.803767Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:24:39.865056Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:25:39.902436Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:26:39.956260Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:27:39.976707Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:28:39.998444Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:29:40.017379Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:30:40.078333Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:31:40.117039Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:32:40.178162Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:33:40.194360Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:34:40.238529Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:35:40.282517Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:36:40.343518Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:37:40.373053Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:38:40.433667Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:39:40.494387Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:40:40.524210Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:41:40.559413Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:42:40.560365Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:43:40.621503Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:44:40.682682Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:45:40.743276Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:46:40.771107Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:47:40.804994Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:48:40.837534Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:49:40.898682Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:50:40.959200Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:51:41.020033Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:52:41.080743Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:53:41.126600Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:54:41.187124Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:55:41.248123Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:56:41.309501Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:57:41.369233Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:58:41.429947Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T08:59:41.450339Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:00:41.511369Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:01:41.566662Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:02:41.628297Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:03:41.689835Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:04:41.726435Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:05:41.787143Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:06:41.847272Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:07:41.907188Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:08:41.967224Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:09:42.028288Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:10:42.089483Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:11:42.150357Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:12:42.211569Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:13:42.272931Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:14:42.334252Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:15:42.395125Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:16:42.456064Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:17:42.516601Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:18:42.577415Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:19:42.638280Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:20:42.699096Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:21:42.760297Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:22:42.821605Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:23:42.882700Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:24:42.943223Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:25:43.003866Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:26:43.064640Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:27:43.125811Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:28:43.186172Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:29:43.234876Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:30:43.296513Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:31:43.307215Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:32:43.313326Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:33:43.374197Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:34:43.435309Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:35:43.442493Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:36:43.486432Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:37:43.520283Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:38:43.579247Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:39:43.614427Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:40:43.648664Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:41:43.710306Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:42:43.771240Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:43:43.816906Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:44:43.877929Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:45:43.934500Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:46:43.995801Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:47:44.034600Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:48:44.091327Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:49:44.152311Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:50:44.169434Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:51:44.230899Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:52:44.267446Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:53:44.328785Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:54:44.373227Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:55:44.433385Z | Info | Live bytes: 768.93MB Heap size: 2677.01MB +2024-07-15T09:55:59.775790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:56:31.279492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:56:44.438283Z | Info | Live bytes: 1181.81MB Heap size: 2677.01MB +2024-07-15T09:57:21.843987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:57:44.446476Z | Info | Live bytes: 1207.10MB Heap size: 2677.01MB +2024-07-15T09:57:45.890454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:57:48.205800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:57:51.502159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:57:52.201816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:57:55.781123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:00.681913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:01.706721Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Value.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/StakePoolMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Address.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/DRepMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-07-15T09:58:04.804951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:33.030267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:40.256626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:40.691633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:41.755748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:42.609490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:43.405373Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T09:58:44.449472Z | Info | Live bytes: 942.89MB Heap size: 2900.36MB +2024-07-15T09:58:52.218470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T09:58:58.428029Z | Info | LSP: received shutdown +2024-07-15T09:58:58.429052Z | Error | Got EOF +2024-07-15T09:59:24.126399Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-15T09:59:24.127483Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15T09:59:24.127802Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T09:59:24.131402Z | Info | Logging heap statistics every 60.00s +2024-07-15T09:59:24.139696Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T09:59:24.140047Z | Info | Starting server +2024-07-15T09:59:54.473496Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-15T09:59:54.535630Z | Info | Started LSP server in 30.40s +2024-07-15T09:59:59.738138Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-15T09:59:59.739447Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-15T10:00:00.178043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:00:01.353133Z | Info | Load cabal cradle using single file +2024-07-15T10:00:02.289111Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT292350-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-15T10:00:09.430894Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-c875534007e32f9c29d109be7ba71e4921e24ed2 +2024-07-15T10:00:09.436582Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-15T10:00:24.142393Z | Info | Live bytes: 680.62MB Heap size: 1824.52MB +2024-07-15T10:00:39.579667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:00:42.085335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:00:42.599140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:00:43.660835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:01:04.242906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:01:05.204728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:01:15.565391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:01:24.151052Z | Info | Live bytes: 635.05MB Heap size: 2366.64MB +2024-07-15T10:01:37.079332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:01:37.539595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:01:38.024235Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Value.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/StakePoolMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Address.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/DRepMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-07-15T10:02:11.402915Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Value.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/StakePoolMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Address.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/DRepMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-07-15T10:02:15.243899Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T10:02:15.626999Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T10:02:24.158367Z | Info | Live bytes: 973.38MB Heap size: 2366.64MB +2024-07-15T10:03:24.178205Z | Info | Live bytes: 973.38MB Heap size: 2366.64MB +2024-07-15T10:04:24.238676Z | Info | Live bytes: 973.38MB Heap size: 2366.64MB +2024-07-15T10:05:24.243871Z | Info | Live bytes: 973.38MB Heap size: 2366.64MB +2024-07-15T10:05:37.501536Z | Info | LSP: received shutdown +2024-07-15T10:05:37.504019Z | Error | Got EOF +2024-07-15T10:06:59.347390Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-15T10:06:59.348629Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15T10:06:59.348947Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T10:06:59.351875Z | Info | Logging heap statistics every 60.00s +2024-07-15T10:06:59.359993Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T10:06:59.360464Z | Info | Starting server +2024-07-15T10:07:59.413395Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:08:59.441170Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:09:59.460718Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:10:59.468116Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:11:59.529866Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:12:59.592039Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:13:59.613287Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:14:59.674191Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:15:59.684255Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:16:59.745163Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:17:59.806636Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:18:59.808348Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:19:59.823812Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:20:59.866342Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:21:59.876664Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:22:59.937349Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:23:59.953168Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:25:00.014225Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:26:00.025036Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:27:00.085599Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:28:00.146218Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:29:00.197454Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:30:00.250952Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:31:00.259137Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:32:00.281320Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:33:00.341232Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:34:00.401195Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:35:00.461926Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:36:00.522285Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:37:00.545286Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:38:00.574085Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:39:00.634260Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:40:00.686449Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-15T10:40:01.152540Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-15T10:40:01.203822Z | Info | Started LSP server in 33m02s +2024-07-15T10:40:09.963701Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-15T10:40:09.964535Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-15T10:40:10.388127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:40:10.388153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:40:11.470289Z | Info | Load cabal cradle using single file +2024-07-15T10:40:12.416808Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT300680-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-15T10:40:19.542782Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-bee3f6afd6f755832fc6ad2fc28aff612b50108d +2024-07-15T10:40:19.547813Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-15T10:40:31.175260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:40:34.319820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:40:35.818245Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:40:42.161261Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-15T10:40:43.156095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:40:51.069252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:41:00.694039Z | Info | Live bytes: 833.10MB Heap size: 2190.48MB +2024-07-15T10:41:33.687203Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:41:34.144917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:41:49.498163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:42:00.701389Z | Info | Live bytes: 833.10MB Heap size: 2190.48MB +2024-07-15T10:42:34.751567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:43:00.718942Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:44:00.779980Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:45:00.841192Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:46:00.901430Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:47:00.958568Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:48:00.960381Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:49:01.021705Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:50:01.082698Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:51:01.143867Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:52:01.150485Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:53:01.182446Z | Info | Live bytes: 999.38MB Heap size: 2190.48MB +2024-07-15T10:53:31.655263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:54:01.194201Z | Info | Live bytes: 1015.12MB Heap size: 2190.48MB +2024-07-15T10:55:01.255345Z | Info | Live bytes: 1015.12MB Heap size: 2190.48MB +2024-07-15T10:56:01.316837Z | Info | Live bytes: 1015.12MB Heap size: 2190.48MB +2024-07-15T10:57:01.378197Z | Info | Live bytes: 1015.12MB Heap size: 2190.48MB +2024-07-15T10:57:10.741102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:12.861183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:25.003777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:25.498752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:26.834144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:26.906990Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:26.979362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:27.477921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:27.689309Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:27.851815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:27.960503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:28.082061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:28.332744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:28.820466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:30.030032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:30.736650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:31.636335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:32.062454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:40.302756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:40.576605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:40.886811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:41.512077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:41.842054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:42.074630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:42.214271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:42.232672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:42.346288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:42.490981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:42.712253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:42.855168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:42.969684Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:43.149300Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:43.226933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:43.351358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:43.427315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:43.489790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:43.581976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:43.718510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:44.920261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:45.078205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:45.108582Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:45.257553Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:45.365178Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:45.617246Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:45.629385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:45.816408Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:46.190240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:47.142005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:47.426634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:48.483436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:52.884472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:55.949560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:56.663192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:56.862805Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:56.940431Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:57:57.252279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:57.703294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:58.176322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:57:58.206815Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:57:58.782220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:01.382310Z | Info | Live bytes: 681.04MB Heap size: 2670.72MB +2024-07-15T10:58:05.816752Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:58:05.908843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:05.982048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:58:06.045857Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:58:06.129850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:58:06.167907Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:58:06.357596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:06.738840Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:58:06.872480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:07.314608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:28.559499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:29.201428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:29.962341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:30.320290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:58:30.386576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:30.900837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:31.387483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:31.902340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:32.990602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:34.001061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:43.348120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:47.879691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:49.993218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:50.532093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:51.947116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:52.237887Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:58:55.700781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:58:58.226367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:01.386349Z | Info | Live bytes: 975.21MB Heap size: 2670.72MB +2024-07-15T10:59:08.437528Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:08.493112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:08.607417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:08.793634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:10.659093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:11.273480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:11.872278Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:11.999722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:12.194255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:13.147131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:13.201055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:13.564158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:13.977112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:14.453087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:15.114838Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:59:15.690486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:25.675383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:28.276582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:29.366339Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:29.420187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:29.511623Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:29.573699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:29.715505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T10:59:29.742406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:30.442010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:31.812020Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:59:32.272601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:34.084026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:34.771126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:35.101119Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:59:41.662490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:42.817370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:42.990312Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T10:59:43.564368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T10:59:54.895429Z | Info | LSP: received shutdown +2024-07-15T10:59:54.897795Z | Error | Got EOF +2024-07-15T10:59:54.897915Z | Info | Reactor thread stopped +2024-07-15T10:59:59.969406Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-15T10:59:59.970493Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15T10:59:59.970803Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T10:59:59.973412Z | Info | Logging heap statistics every 60.00s +2024-07-15T10:59:59.980041Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T10:59:59.980663Z | Info | Starting server +2024-07-15T10:59:59.981949Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-15T11:00:00.050463Z | Info | Started LSP server in 0.07s +2024-07-15T11:00:01.285484Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Script.hs +2024-07-15T11:00:01.287059Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-15T11:00:01.737936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:01.737943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:02.866690Z | Info | Load cabal cradle using single file +2024-07-15T11:00:03.831023Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT338680-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-15T11:00:07.354823Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-bee3f6afd6f755832fc6ad2fc28aff612b50108d +2024-07-15T11:00:07.359625Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-15T11:00:38.445357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:40.492149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:40.630572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:40.675436Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:40.877153Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:40.970614Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:41.056397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:41.090471Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:41.473024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:42.013171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:42.212211Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:42.499003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:42.524831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:43.041408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:44.201124Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:44.671117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:45.115662Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:45.231217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:45.384156Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:00:45.491874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:45.925702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:46.500111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:50.398012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:50.839096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:51.283127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:52.133034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:53.355884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:55.370542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:55.800182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:56.270071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:57.022041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:57.485167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:57.926730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:00:59.976908Z | Info | Live bytes: 559.21MB Heap size: 2198.86MB +2024-07-15T11:01:01.781822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:02.803531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:05.092173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:11.773021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:13.604901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:14.040263Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:01:14.178809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:14.601256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:15.133710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:16.749472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:17.889228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:20.838685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:25.864785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:40.547005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:52.525243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:54.983416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:56.409134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:57.347461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:01:59.981459Z | Info | Live bytes: 572.48MB Heap size: 2198.86MB +2024-07-15T11:02:04.562537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:09.459675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:11.375208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:11.866631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:12.938275Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T11:02:38.566406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:39.240624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:39.505802Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T11:02:40.958711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:41.426083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:41.870152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:42.381239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:42.819379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:43.053886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:02:43.246390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:43.710725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:44.814843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:45.294227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:45.747557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:46.314484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:46.746088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:47.169101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:49.135184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:49.665054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:50.110567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:50.582834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:51.067134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:51.519606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:51.966099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:52.228909Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:02:52.453343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:52.756801Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T11:02:53.329530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:02:59.984471Z | Info | Live bytes: 597.24MB Heap size: 2198.86MB +2024-07-15T11:04:00.028436Z | Info | Live bytes: 603.87MB Heap size: 2198.86MB +2024-07-15T11:05:00.089684Z | Info | Live bytes: 603.87MB Heap size: 2198.86MB +2024-07-15T11:05:18.270260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:05:19.767443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:05:19.870248Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:05:19.951570Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:05:20.103398Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:05:20.136204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:05:20.244589Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:05:20.307112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:05:20.427565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T11:05:20.609916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:05:23.513434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:05:23.986059Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T11:05:24.556789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T11:06:00.093705Z | Info | Live bytes: 607.27MB Heap size: 2198.86MB +2024-07-15T11:07:00.154317Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:08:00.205982Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:09:00.266232Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:10:00.326159Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:11:00.386276Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:12:00.446114Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:13:00.506295Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:14:00.558335Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:15:00.619312Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:16:00.679159Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:17:00.703696Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:18:00.764845Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:19:00.825853Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:20:00.886059Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:21:00.946222Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:22:01.006831Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:23:01.067070Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:24:01.127693Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:25:01.184390Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:26:01.244219Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:27:01.304852Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:28:01.355118Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:29:01.415228Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:30:01.430367Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:31:01.438468Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:32:01.487314Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:33:01.502359Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:34:01.505484Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:35:01.566454Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:36:01.598440Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:37:01.627735Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:38:01.662470Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:39:01.723727Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:40:01.769268Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:41:01.830256Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:42:01.859677Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:43:01.907075Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:44:01.921445Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:45:01.968743Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:46:01.988842Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:47:02.014410Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:48:02.016483Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:49:02.074201Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:50:02.076274Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:51:02.078421Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:52:02.139813Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:53:02.201442Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:54:02.221347Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:55:02.282796Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:56:02.311338Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:57:02.342783Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:58:02.404090Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T11:59:02.465465Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:10:25.189356Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:11:25.208587Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:12:25.240234Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:13:25.301480Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:14:25.321803Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:15:25.382970Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:16:25.444684Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:17:25.488184Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:18:25.507684Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:19:25.514536Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:20:25.541991Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:21:25.560004Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:22:25.571593Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:23:25.633830Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:24:25.695685Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:25:25.756852Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:26:25.818097Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:27:25.879234Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:28:25.914300Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:29:25.975262Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:30:26.016444Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:31:26.077293Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:32:26.138270Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:33:26.176575Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:34:26.237775Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:35:26.296402Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:36:26.320606Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:37:26.381986Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:38:26.443034Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:39:26.503837Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:40:26.564999Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:41:26.625722Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:42:26.685386Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:43:26.746163Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:44:26.807125Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:45:26.868422Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:46:26.908199Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:47:26.969084Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:48:27.030124Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:49:27.091307Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:50:27.152252Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:51:27.212982Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:52:27.257524Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:53:27.317228Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:54:27.377987Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:55:27.439195Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:56:27.500285Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:57:27.560955Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:58:27.598043Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T15:59:27.658836Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:00:27.719622Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:01:27.780460Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:02:27.816769Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:03:27.877444Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:04:27.938131Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:05:27.998820Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:06:28.059832Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:07:28.121372Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:08:28.132013Z | Info | Live bytes: 605.27MB Heap size: 2198.86MB +2024-07-15T16:09:05.499924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:06.882477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:08.084699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:08.847624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:09.878862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:10.350263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:10.765803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:11.671855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:12.152653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:12.749027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:13.387394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:13.880621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:14.342545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:15.142717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:15.589452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:16.020337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:16.638686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:17.060309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:09:28.139757Z | Info | Live bytes: 613.83MB Heap size: 2198.86MB +2024-07-15T16:09:52.863623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:05.903369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:06.548451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:14.424106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:16.432029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:16.965731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:17.726184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:18.505853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:20.241495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:10:20.297130Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:10:20.373515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:10:20.594289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:21.777125Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:10:28.145335Z | Info | Live bytes: 629.37MB Heap size: 2198.86MB +2024-07-15T16:10:35.421044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:37.222829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:39.806733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:10:39.841197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:39.863515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:10:40.350917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:40.850028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:45.685285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:46.384955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:46.609982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:10:46.689934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:10:46.866637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:50.575330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:57.685940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:10:58.472077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:07.049584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:11:07.174708Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:11:07.257304Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:11:07.364324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:11:07.419938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:08.217809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:08.740884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:09.352049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:09.844185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:10.603182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:11.630372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:12.100002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:12.888969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:13.344161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:13.819663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:16.388409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:16.819288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:19.564937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:20.581039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:21.440487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:27.464370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:11:27.628071Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:11:27.823466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:28.132094Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:11:28.146634Z | Info | Live bytes: 640.56MB Heap size: 2198.86MB +2024-07-15T16:11:42.839420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:43.345964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:48.253975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:11:48.710148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:12:28.172634Z | Info | Live bytes: 672.54MB Heap size: 2198.86MB +2024-07-15T16:13:28.217530Z | Info | Live bytes: 672.54MB Heap size: 2198.86MB +2024-07-15T16:14:28.278677Z | Info | Live bytes: 672.54MB Heap size: 2198.86MB +2024-07-15T16:14:50.501915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:14:52.100809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:14:53.497964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:14:53.944375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:14:54.548713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:14:54.742897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:14:54.900371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:14:56.492719Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:14:56.597191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:15:21.477374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:15:28.285355Z | Info | Live bytes: 690.72MB Heap size: 2198.86MB +2024-07-15T16:16:28.346334Z | Info | Live bytes: 690.72MB Heap size: 2198.86MB +2024-07-15T16:16:49.427462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:16:56.937309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:16:57.898773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:16:58.853925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:16:59.710188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:00.818227Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:00.871017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:00.956861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:01.411868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:02.359994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:02.449847Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:02.622085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:03.124515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:06.915268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:07.367560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:09.931273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:10.033812Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:10.078003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:10.186895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:10.554556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:11.620940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:12.474364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:13.581331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:14.258953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:14.764048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:26.765746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:26.859067Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:27.014885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:27.064006Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:27.207523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:27.290862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:27.405708Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:27.427936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:27.884502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:28.348158Z | Info | Live bytes: 734.64MB Heap size: 2198.86MB +2024-07-15T16:17:28.393431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:29.104764Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:29.158981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:29.449562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:29.903329Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:50.232637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:50.330349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:50.385909Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:50.451664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:50.537092Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:50.763241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:50.812296Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:50.897561Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:50.969839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:51.041504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:51.163554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:51.185793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:51.390257Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:51.527375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:51.650484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:51.770350Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:51.789600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:52.432777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:52.530675Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:52.658940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:52.831552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:53.026595Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:17:53.601680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:57.495217Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:57.654399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:17:57.839876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:58.302117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:59.181412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:17:59.604934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:10.521683Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:10.557021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:11.143961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:11.804674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:14.080777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:14.158734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:14.516048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:14.990445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:17.111945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:17.591563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:18.084363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:18.591032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:22.368316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:22.475801Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:22.545304Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:22.808259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:23.125123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:24.392686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:24.893740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:25.184037Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:25.545018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:26.081232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:26.599062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:28.350403Z | Info | Live bytes: 609.81MB Heap size: 2657.09MB +2024-07-15T16:18:42.252117Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:42.304646Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:18:42.542356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:43.855985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:44.842438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:56.683957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:57.200198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:57.615680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:18:58.137631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:01.709934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:02.751263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:02.933966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:19:03.294682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:06.488588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:09.532854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:10.067205Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:19:19.238788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:20.353900Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:19:28.355684Z | Info | Live bytes: 645.00MB Heap size: 2657.09MB +2024-07-15T16:19:49.626094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:50.183627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:50.873111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:19:52.119710Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:20:01.176011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:01.704674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:05.190079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:05.698767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:05.780578Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:20:14.320987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:14.744692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:14.793646Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:20:28.360536Z | Info | Live bytes: 1369.95MB Heap size: 2862.61MB +2024-07-15T16:20:50.930656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:51.492948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:52.315356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:20:52.673334Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:02.003330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:06.263883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:06.857108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:06.926004Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:10.763770Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:10.947629Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ ] +2024-07-15T16:21:11.154513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:11.614358Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:11.636520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:16.631934Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:16.778370Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ ] +2024-07-15T16:21:17.027683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:17.402242Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:17.466149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:20.359833Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:20.517827Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ ] +2024-07-15T16:21:20.758906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:21.124316Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:21:21.220513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:28.363407Z | Info | Live bytes: 831.97MB Heap size: 3321.89MB +2024-07-15T16:21:29.509215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:33.107336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:39.641595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:40.522275Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:21:40.632629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:40.651585Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:21:40.717249Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:21:40.783263Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:21:40.830829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:21:41.100689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:41.920405Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:21:42.067990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:55.274581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:55.996513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:21:56.046375Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:22:28.389605Z | Info | Live bytes: 1372.95MB Heap size: 3321.89MB +2024-07-15T16:23:28.403558Z | Info | Live bytes: 1372.95MB Heap size: 3321.89MB +2024-07-15T16:24:28.456535Z | Info | Live bytes: 1372.95MB Heap size: 3321.89MB +2024-07-15T16:25:06.549075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:25:07.864502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:25:08.479069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:25:09.174298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:25:28.472239Z | Info | Live bytes: 879.52MB Heap size: 3321.89MB +2024-07-15T16:26:28.500719Z | Info | Live bytes: 888.96MB Heap size: 3321.89MB +2024-07-15T16:27:28.561268Z | Info | Live bytes: 904.10MB Heap size: 3321.89MB +2024-07-15T16:27:53.722887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:27:54.719978Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:17.631733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:18.446103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:27.941722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:28.563278Z | Info | Live bytes: 942.77MB Heap size: 3321.89MB +2024-07-15T16:28:29.025357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:31.230306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:40.764440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:45.353447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:56.554400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:28:59.411293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:29:00.049547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:29:01.339833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:29:01.845130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:29:02.465783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:29:03.651675Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:29:04.120547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:29:05.886003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:29:28.582155Z | Info | Live bytes: 976.16MB Heap size: 3321.89MB +2024-07-15T16:30:28.643390Z | Info | Live bytes: 976.16MB Heap size: 3321.89MB +2024-07-15T16:31:28.704502Z | Info | Live bytes: 976.16MB Heap size: 3321.89MB +2024-07-15T16:32:28.765383Z | Info | Live bytes: 976.16MB Heap size: 3321.89MB +2024-07-15T16:33:28.774340Z | Info | Live bytes: 976.16MB Heap size: 3321.89MB +2024-07-15T16:34:28.797917Z | Info | Live bytes: 976.16MB Heap size: 3321.89MB +2024-07-15T16:34:53.381193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:53.918132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:55.748506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:56.261118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:56.739892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:57.182897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:57.770437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:58.293035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:58.791902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:59.409473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:34:59.937998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:00.884389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:01.135040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:01.502944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:02.060161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:02.943345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:03.361479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:04.387563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:04.860232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:07.138762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:08.110438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:11.832089Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:11.957788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:12.021743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:12.097536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:12.281495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:12.453183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:13.308512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:14.486729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:18.061606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.139905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:18.212960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.285399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.328701Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.376226Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.587267Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:18.670277Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.746672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.853526Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:18.913294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:19.005301Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:19.041708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:19.474797Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:19.671888Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:19.814332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:19.875423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:19.924491Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:19.987682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:20.076897Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:35:20.326787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:20.732131Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:35:20.818583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:21.308632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:28.498295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:28.799337Z | Info | Live bytes: 1190.49MB Heap size: 3321.89MB +2024-07-15T16:35:29.875085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:34.389168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:37.951252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:38.406361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:38.591357Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:35:42.192020Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:35:42.595562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:35:43.349878Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:35:43.755340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:08.970110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:13.078007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:28.811348Z | Info | Live bytes: 902.35MB Heap size: 3321.89MB +2024-07-15T16:36:39.597639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:41.470393Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:47.351333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:48.105101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:48.915511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:49.503324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:36:49.729165Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:36:50.309111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:37:01.165971Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:37:01.242545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:37:01.311612Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:37:01.510447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:37:03.507301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:37:05.401909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:37:28.833640Z | Info | Live bytes: 933.99MB Heap size: 3321.89MB +2024-07-15T16:37:32.443647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:37:33.155356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:37:33.638520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:37:34.020731Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:38:28.843342Z | Info | Live bytes: 1279.28MB Heap size: 3321.89MB +2024-07-15T16:38:30.760722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:38:31.240025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:38:31.523249Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:38:40.370571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:38:55.106711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:38:55.377016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:55.439163Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:55.516481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:55.666867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:38:55.822806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:55.944344Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:56.143848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:56.181586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:38:56.238759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:56.391628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:56.603520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:38:56.605933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:38:57.208727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:15.729145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:15.996403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:16.592317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:16.718803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:16.834534Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:16.893710Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:16.963107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:17.823970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:17.988253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:18.021635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:18.116352Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:18.209504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:18.376060Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:18.489595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:18.560708Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:18.763331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:18.852495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:18.931157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:18.953490Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:19.041787Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:19.352761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:19.409594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:19.443081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:19.695084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:19.803126Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:19.910068Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:19.994712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:20.054548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:20.063592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:20.205386Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:20.333449Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:20.429797Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:20.532937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:20.575189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:20.673503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:20.800402Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:21.038725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:21.362468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:21.677042Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:21.727651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:21.792428Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:22.026109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:22.136590Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:22.174332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:22.236697Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:22.287635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:22.349571Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:39:22.608829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:23.634857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:28.844995Z | Info | Live bytes: 926.68MB Heap size: 3321.89MB +2024-07-15T16:39:30.206830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:33.229247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:34.015624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:37.175913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:39:37.386257Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:40:02.403939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:02.946136Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:40:03.003304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:20.744915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:21.300776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:23.475877Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:40:23.573074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:24.066655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:28.271561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:28.846577Z | Info | Live bytes: 1419.79MB Heap size: 3321.89MB +2024-07-15T16:40:32.612916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:38.050152Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-15T16:40:38.273167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:39.404824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:39.886015Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:40:48.496179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:48.930256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:40:49.051465Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:41:08.312647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:08.879271Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-15T16:41:08.893187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:25.998190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:26.652101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:27.072019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:27.530164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:27.952190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:28.371844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:28.847706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:28.848000Z | Info | Live bytes: 1306.41MB Heap size: 3321.89MB +2024-07-15T16:41:29.065349Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-15T16:41:30.709607Z | Info | LSP: received shutdown +2024-07-15T16:41:30.710826Z | Error | Got EOF +2024-07-15 16:41:37.4100000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-15 16:41:37.4100000 [client] INFO Finding haskell-language-server +2024-07-15 16:41:37.4110000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:37.4110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:37.4170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-15 16:41:37.8320000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:37.8320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:37.8400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-15 16:41:37.9560000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:37.9560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:37.9600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-15 16:41:38.1570000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:38.1570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:38.1630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-15 16:41:38.2980000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:38.2980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:38.3060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-15 16:41:38.3230000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:38.3230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:38.3280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-15 16:41:38.3420000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:38.3420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:38.3460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-15 16:41:38.3640000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-15 16:41:38.4080000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:38.4080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:38.4130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-15 16:41:38.5080000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-15 16:41:38.5090000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-15 16:41:45.1960000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-15 16:41:45.4640000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-15 16:41:45.4640000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:45.4640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:45.4710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-15 16:41:45.5570000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:45.5570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:45.5610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-15 16:41:45.5760000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:45.5760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:45.5810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-15 16:41:45.5940000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:45.5950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:45.6010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-15 16:41:45.6160000 [client] INFO Checking for ghcup installation +2024-07-15 16:41:45.6160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 16:41:45.6230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-15 16:41:45.7180000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-15 16:41:45.7180000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-15 16:41:45.7180000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-15 16:41:45.7180000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15 16:41:45.7180000 [client] INFO server environment variables: +2024-07-15 16:41:45.7180000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-15 16:41:45.7180000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-15 16:41:45.7180000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-15 16:41:45.7190000 [client] INFO Starting language server +2024-07-15T16:41:55.540068Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-15T16:41:55.541076Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15T16:41:55.541273Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T16:41:55.544329Z | Info | Logging heap statistics every 60.00s +2024-07-15T16:41:55.551507Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T16:41:55.551919Z | Info | Starting server +2024-07-15T16:41:55.553343Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-15T16:41:55.620888Z | Info | Started LSP server in 0.07s +2024-07-15T16:41:57.032380Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-15T16:41:57.033837Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-15T16:41:57.459268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:57.459309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T16:41:58.760483Z | Info | Load cabal cradle using single file +2024-07-15T16:41:59.818218Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT492482-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-15T16:42:03.820406Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-bee3f6afd6f755832fc6ad2fc28aff612b50108d +2024-07-15T16:42:03.827953Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-15T16:42:55.575445Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:43:55.636678Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:44:55.698133Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:45:55.759477Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:46:55.820800Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:47:55.882021Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:48:55.943428Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:49:56.004450Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:50:56.065607Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:51:56.126937Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:52:56.187915Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:53:56.249263Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:54:56.307283Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:55:56.332176Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:56:56.386901Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:57:56.393453Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:58:56.454857Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T16:59:56.458310Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:00:56.479640Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:01:56.509959Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:02:56.551882Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:03:56.584587Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:04:56.645777Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:05:56.688635Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:06:56.718450Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:07:56.735048Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:08:56.746267Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:09:56.807756Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:10:56.814635Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:11:56.875559Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:12:56.924444Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:13:56.936279Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:14:56.997488Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:15:57.058485Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:16:57.060863Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:17:57.092642Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:18:57.150520Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:19:57.175234Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:20:57.235256Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:21:57.278283Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:22:57.339195Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:23:57.399384Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:24:57.409443Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:25:57.469333Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:26:57.530031Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:27:57.590390Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:28:57.650302Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:29:57.710366Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:30:57.770165Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:31:57.778517Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:32:57.796548Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:33:57.806563Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:34:57.832365Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:35:57.847026Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:36:57.905592Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:37:57.954322Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:38:57.964534Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:39:58.026428Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:40:58.087790Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:41:58.138333Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:42:58.161274Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:43:58.222410Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:44:58.283644Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:45:58.344850Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:46:58.406021Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:47:58.466867Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:48:58.527266Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:49:58.552462Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:50:58.561482Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:51:58.622760Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:52:58.683928Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:53:58.690790Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:54:58.701719Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:55:58.762944Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:56:58.824275Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:57:58.885647Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:58:58.939426Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T17:59:59.000614Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:00:59.061395Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:01:59.122028Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:02:59.183153Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:03:59.205508Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:04:59.264893Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:05:59.325420Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:06:59.386753Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:07:59.429570Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:08:59.436341Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:09:59.488590Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:10:59.515268Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:11:59.571646Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:12:59.578130Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:13:59.638396Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:14:59.651218Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:15:59.653907Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:16:59.714488Z | Info | Live bytes: 502.23MB Heap size: 1774.19MB +2024-07-15T18:17:41.499912Z | Info | LSP: received shutdown +2024-07-15T18:17:41.501349Z | Info | Reactor thread stopped +2024-07-15T18:17:41.502617Z | Error | Got EOF +2024-07-15 18:17:48.9490000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-15 18:17:48.9490000 [client] INFO Finding haskell-language-server +2024-07-15 18:17:48.9500000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:48.9500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:48.9580000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-15 18:17:49.2640000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:49.2640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:49.2690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-15 18:17:49.3860000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:49.3860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:49.3920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-15 18:17:49.5220000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:49.5230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:49.5280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-15 18:17:49.6590000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:49.6590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:49.6640000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-15 18:17:49.6790000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:49.6790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:49.6850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-15 18:17:49.7000000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:49.7000000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:49.7050000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-15 18:17:49.7260000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-15 18:17:49.7620000 [client] INFO Checking for ghcup installation +2024-07-15 18:17:49.7620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 18:17:49.7660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-15 18:17:49.8710000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-15 18:17:49.8720000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-15 19:17:37.8780000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-15 19:17:37.8790000 [client] INFO Finding haskell-language-server +2024-07-15 19:17:37.8810000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:37.8810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:37.8920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-15 19:17:38.3740000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:38.3740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:38.3800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-15 19:17:38.5160000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:38.5160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:38.5230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-15 19:17:38.6610000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:38.6610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:38.6670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-15 19:17:38.8200000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:38.8200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:38.8250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-15 19:17:38.8400000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:38.8400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:38.8470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-15 19:17:38.8630000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:38.8640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:38.8720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-15 19:17:38.9000000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-15 19:17:38.9600000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:38.9600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:38.9660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-15 19:17:39.0810000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-15 19:17:39.0820000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-15 19:17:41.4240000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-15 19:17:41.7360000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-15 19:17:41.7360000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:41.7360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:41.7460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-15 19:17:41.9240000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:41.9250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:41.9340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-15 19:17:41.9600000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:41.9600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:41.9690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-15 19:17:41.9850000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:41.9860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:41.9940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-15 19:17:42.0110000 [client] INFO Checking for ghcup installation +2024-07-15 19:17:42.0110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-15 19:17:42.0190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-15 19:17:42.2060000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-15 19:17:42.2060000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-15 19:17:42.2060000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-15 19:17:42.2070000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15 19:17:42.2070000 [client] INFO server environment variables: +2024-07-15 19:17:42.2070000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-15 19:17:42.2070000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-15 19:17:42.2070000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-15 19:17:42.2080000 [client] INFO Starting language server +2024-07-15T19:17:53.374373Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-15T19:17:53.375411Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-15T19:17:53.375576Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T19:17:53.377947Z | Info | Logging heap statistics every 60.00s +2024-07-15T19:17:53.384698Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-15T19:17:53.385070Z | Info | Starting server +2024-07-15T19:17:53.386897Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-15T19:17:53.434831Z | Info | Started LSP server in 0.05s +2024-07-15T19:17:55.354900Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-15T19:17:55.356858Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-15T19:17:55.911865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-15T19:17:57.227400Z | Info | Load cabal cradle using single file +2024-07-15T19:17:58.449328Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT560943-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-15T19:18:03.084593Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-bee3f6afd6f755832fc6ad2fc28aff612b50108d +2024-07-15T19:18:03.094762Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-15T19:18:53.421192Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:19:53.482335Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:20:53.543537Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:21:53.604381Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:22:53.665396Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:23:53.726583Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:24:53.787553Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:25:53.848658Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:26:53.880459Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:27:53.941542Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:28:54.003216Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:31:17.608785Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:32:17.669621Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:33:17.730423Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:34:17.789925Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:35:17.850542Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:36:17.910416Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:37:17.924218Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:38:17.968950Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:39:17.978861Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:40:18.039528Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:41:18.099605Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:42:18.134425Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:43:18.194585Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:44:18.197803Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:45:18.215672Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:46:18.256259Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:47:18.317529Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:48:18.379264Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:49:18.390846Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:50:18.408762Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:51:18.424329Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:52:18.463543Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:53:18.523661Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:54:18.584699Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:55:18.643053Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:56:18.684611Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:57:18.745344Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:58:18.802739Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T19:59:18.863538Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:00:18.923463Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:01:18.983575Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:02:19.044401Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:03:19.104419Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:04:19.165010Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:05:19.204476Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:06:19.212029Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:07:19.272621Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:08:19.293508Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:09:19.303129Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:10:19.329211Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:11:19.388260Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:12:19.422683Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:13:19.447398Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:14:19.487518Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:15:19.548400Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:16:19.608638Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:17:19.669569Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:18:19.680147Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:19:19.741139Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:20:19.771017Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:21:19.809307Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:22:19.870132Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:23:19.930539Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:24:19.934467Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:25:19.995383Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:26:20.056169Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:27:20.116445Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:28:20.168581Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:29:20.228712Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:30:20.241172Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:31:20.302206Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:32:20.344244Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:33:20.404970Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:34:20.454873Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:35:20.515492Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:36:20.535436Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:37:20.576761Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:38:20.593280Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:39:20.640761Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:40:20.653351Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:41:20.714126Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:42:20.744266Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:43:20.790697Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:44:20.819578Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:45:20.828118Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:46:20.830281Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:47:20.891447Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:48:20.951563Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:49:20.979579Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:50:21.040529Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:51:21.056966Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:52:21.117464Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:53:21.177619Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:54:21.223670Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:55:21.278152Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:56:21.338922Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:57:21.398495Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:58:21.459520Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T20:59:21.519205Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:00:21.580080Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:01:21.640635Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:02:21.700662Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:03:21.758767Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:04:21.796729Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:05:21.857216Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:06:21.887242Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:07:21.899434Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:08:21.959600Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:09:21.966664Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:10:22.027750Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:11:22.035477Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:12:22.096755Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:13:22.148088Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:14:22.182892Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:15:22.243488Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:16:22.256339Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:17:22.280759Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:18:22.341537Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:19:22.401511Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:20:22.421577Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:21:22.441620Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:22:22.502254Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:23:22.563380Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:24:22.623602Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:25:22.683505Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:26:22.693764Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:27:22.725544Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:28:22.742049Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:29:22.803122Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:30:22.863527Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:31:22.900820Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:32:22.960776Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:33:23.020440Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:34:23.081103Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:35:23.096250Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:36:23.156466Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:37:23.217173Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:38:23.278453Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:39:23.339579Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:40:23.371521Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:41:23.433169Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:42:23.494903Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:43:23.555540Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:44:23.616714Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:45:23.678387Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:46:23.740022Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:47:23.802189Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:48:23.863797Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:49:23.925263Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:50:23.986483Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:51:24.047693Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:52:24.108910Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:53:24.169998Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:54:24.231419Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:55:24.254953Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:56:24.316473Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:57:24.378085Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:58:24.439547Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T21:59:24.500998Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T22:00:24.561567Z | Info | Live bytes: 533.45MB Heap size: 1753.22MB +2024-07-15T22:01:13.422607Z | Error | Got EOF +2024-07-16 06:20:15.9610000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-16 06:20:15.9680000 [client] INFO Finding haskell-language-server +2024-07-16 06:20:15.9700000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:15.9700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:15.9810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-16 06:20:16.6480000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:16.6490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:16.6650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-16 06:20:16.9640000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:16.9650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:16.9730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-16 06:20:17.2190000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:17.2190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:17.2280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-16 06:20:17.4920000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:17.4920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:17.5030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-16 06:20:17.5220000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:17.5220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:17.5290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-16 06:20:17.5600000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:17.5600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:17.5790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-16 06:20:17.6340000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-16 06:20:17.7790000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:17.7790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:17.7900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-16 06:20:18.0490000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-16 06:20:18.0500000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-16 06:20:29.8820000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-16 06:20:30.0120000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-16 06:20:30.0130000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:30.0130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:30.0210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-16 06:20:30.2000000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:30.2000000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:30.2040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-16 06:20:30.2240000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:30.2250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:30.2350000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-16 06:20:30.2550000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:30.2550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:30.2660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-16 06:20:30.2830000 [client] INFO Checking for ghcup installation +2024-07-16 06:20:30.2840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-16 06:20:30.2920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-16 06:20:30.4800000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-16 06:20:30.4810000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-16 06:20:30.4810000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-16 06:20:30.4810000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-16 06:20:30.4810000 [client] INFO server environment variables: +2024-07-16 06:20:30.4820000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-16 06:20:30.4820000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-16 06:20:30.4820000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-16 06:20:30.4850000 [client] INFO Starting language server +2024-07-16T06:20:43.054468Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-16T06:20:43.056994Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-16T06:20:43.057486Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-16T06:20:43.063509Z | Info | Logging heap statistics every 60.00s +2024-07-16T06:20:43.076946Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-16T06:20:43.077462Z | Info | Starting server +2024-07-16T06:20:43.095841Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-16T06:20:43.229968Z | Info | Started LSP server in 0.15s +2024-07-16T06:20:44.712262Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs +2024-07-16T06:20:44.713666Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-16T06:20:45.268462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:20:46.700290Z | Info | Load cabal cradle using single file +2024-07-16T06:20:47.928580Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT11179-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-16T06:20:51.777220Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-bee3f6afd6f755832fc6ad2fc28aff612b50108d +2024-07-16T06:20:51.788330Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-16T06:20:57.655725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:21:01.589849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:21:43.091921Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-16T06:22:43.152611Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-16T06:23:43.212466Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-16T06:23:52.236775Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:23:53.065158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:23:54.431688Z | Info | LSP: received shutdown +2024-07-16T06:23:54.438122Z | Error | Got EOF +2024-07-16T06:24:01.188764Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-16T06:24:01.189736Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-16T06:24:01.190048Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-16T06:24:01.194331Z | Info | Logging heap statistics every 60.00s +2024-07-16T06:24:01.201920Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-16T06:24:01.202284Z | Info | Starting server +2024-07-16T06:24:01.204327Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-16T06:24:01.210165Z | Info | Started LSP server in 0.01s +2024-07-16T06:24:02.765217Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-16T06:24:02.766508Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-16T06:24:03.334189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:24:04.605078Z | Info | Load cabal cradle using single file +2024-07-16T06:24:05.935481Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT14337-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-16T06:24:10.140404Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-bee3f6afd6f755832fc6ad2fc28aff612b50108d +2024-07-16T06:24:10.152937Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-16T06:25:01.241307Z | Info | Live bytes: 499.48MB Heap size: 1727.00MB +2024-07-16T06:26:01.253000Z | Info | Live bytes: 499.48MB Heap size: 1727.00MB +2024-07-16T06:26:39.469728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:39.565827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:39.613133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:39.757221Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:40.197287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:40.203535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:40.497747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:40.916030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:41.046564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:41.046662Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:42.052591Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:42.159162Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:42.264953Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:42.305151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:42.395215Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:42.941161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:42.941297Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:26:43.644312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:57.077652Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:57.216703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:57.221219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:57.397236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:57.643400Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:57.751618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:57.806202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:57.852639Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:57.945159Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:58.097118Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:58.313523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:58.364020Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:58.466247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:58.504171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:59.030919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:59.349264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:59.463056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:59.623202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:26:59.647013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:26:59.790313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:00.315065Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:00.332781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:00.498013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:00.583771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:00.730455Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:00.794264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:00.874382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:01.028147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:01.253476Z | Info | Live bytes: 584.72MB Heap size: 1780.48MB +2024-07-16T06:27:01.772206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:02.138022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:02.272773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:02.338094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:02.363031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:02.568620Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:02.778842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:03.090391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:03.227727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:03.414843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:03.761902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:04.013533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:04.147154Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:04.237796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:04.528981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:04.562046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:04.861043Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:27:05.131634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:07.673935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:11.834365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:14.740863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:27:14.783776Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:27:15.502115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:28:01.265722Z | Info | Live bytes: 580.47MB Heap size: 2145.39MB +2024-07-16T06:29:01.321511Z | Info | Live bytes: 580.47MB Heap size: 2145.39MB +2024-07-16T06:30:01.361839Z | Info | Live bytes: 580.47MB Heap size: 2145.39MB +2024-07-16T06:30:29.512259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:30:47.663444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:31:01.389762Z | Info | Live bytes: 759.95MB Heap size: 2145.39MB +2024-07-16T06:31:46.571653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:31:47.185946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:31:49.486173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:31:50.085825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:31:54.351966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:31:55.248565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:31:57.492506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:32:01.395603Z | Info | Live bytes: 791.38MB Heap size: 2145.39MB +2024-07-16T06:32:10.470542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:32:10.556223Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:32:11.281995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:01.441604Z | Info | Live bytes: 943.33MB Heap size: 2145.39MB +2024-07-16T06:33:12.336421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:48.915407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:54.909675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:55.490959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:56.228564Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:33:56.417436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:57.405931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:57.624906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:33:57.726541Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:33:57.897326Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:33:58.107528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:58.179917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:33:58.431316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:33:58.607494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:33:58.901936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:33:59.610767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:00.900079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:01.443277Z | Info | Live bytes: 573.42MB Heap size: 2735.73MB +2024-07-16T06:34:01.616957Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:01.752477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:02.193692Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:02.752372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:07.153634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:16.210284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:16.788394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:17.663034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:18.502366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:18.502394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:18.625389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:18.830547Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:18.997529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:19.137112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:19.187763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:48.221001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:48.927030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:49.260580Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:49.381578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:49.739192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:50.373257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:51.208830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:52.277381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:57.043478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:34:57.778650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:57.850566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:34:57.890932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:35:01.447736Z | Info | Live bytes: 639.54MB Heap size: 2735.73MB +2024-07-16T06:35:15.937387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:36:01.459704Z | Info | Live bytes: 639.54MB Heap size: 2735.73MB +2024-07-16T06:36:36.949985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:36:37.736378Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:37.883647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:37.979365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:38.270965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:36:38.300641Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:38.840274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:36:38.893881Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:36:39.506223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:36:58.295196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:58.402552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:58.473715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:58.712552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:36:58.790729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:36:59.276838Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:36:59.447725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:01.461257Z | Info | Live bytes: 844.51MB Heap size: 2735.73MB +2024-07-16T06:37:24.196362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:24.858546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:24.877868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:25.219424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:25.777148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:26.574231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:27.255014Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:27.884366Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:27.975861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:28.063895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:28.288816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:28.925751Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:37:34.848111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:46.679881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:47.281276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:48.162066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:51.616601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:51.761020Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:51.956134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:52.082877Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:52.155424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:52.229180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:52.234600Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:37:52.827558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:37:53.427834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:01.464565Z | Info | Live bytes: 940.71MB Heap size: 2735.73MB +2024-07-16T06:38:12.507384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:12.822258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:38:13.152655Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:38:13.277359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:15.502875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:15.653847Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:38:15.752317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:38:16.127596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:17.359473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:17.932321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:18.746686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:19.349690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:39.406622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:40.135831Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:38:40.179881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:44.847217Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:38:45.129582Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:38:45.215982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:53.285286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:38:55.063641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:39:01.467258Z | Info | Live bytes: 846.57MB Heap size: 2883.58MB +2024-07-16T06:40:01.473265Z | Info | Live bytes: 859.88MB Heap size: 2883.58MB +2024-07-16T06:40:25.561106Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:25.708561Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:25.777941Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:25.822569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:25.879816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.139886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.235696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.345725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.397546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:26.448437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.596015Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.718961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.822447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.878042Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:26.975030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:26.978593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:27.604282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:28.258591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:28.557799Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:28.629461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:28.780284Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:28.880409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:28.884805Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:28.968495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:29.043622Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:29.358606Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:40:29.513156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:45.787804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:46.365448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:48.138397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:54.029348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:55.085512Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:55.218795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:55.295020Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:55.598556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:55.846717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:56.371081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:56.407765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:56.567273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:40:57.107468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:40:57.160844Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:41:01.474876Z | Info | Live bytes: 1230.10MB Heap size: 2883.58MB +2024-07-16T06:41:09.823868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:20.736100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:21.091127Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:25.835559Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:26.387738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:26.441522Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:26.812871Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:26.997475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:27.081505Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:27.164096Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:27.197999Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:27.278034Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:27.352193Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:27.636519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:27.999281Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:28.090936Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:28.551614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:28.810905Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:29.368007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:29.593593Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:30.149270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:30.968767Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:31.039138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:31.220282Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:31.288286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:31.327847Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:31.419585Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:31.546051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:31.702066Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:31.784504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:32.241822Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:32.257261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:32.301505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:32.795721Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:41:33.350490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:42.029962Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:42.180760Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:42.477952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:43.821867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:44.091462Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:44.251697Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:44.364906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:41:44.552974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:55.028605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:56.629223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:41:57.195013Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:42:01.478609Z | Info | Live bytes: 773.49MB Heap size: 3084.91MB +2024-07-16T06:42:08.633400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:09.861464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:10.533897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:17.374899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:19.645108Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:42:19.770687Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:42:19.840582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:19.847322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:42:19.931935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:42:19.987016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:42:20.445981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:20.573464Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:42:21.614981Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:42:21.851428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:25.800471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:28.204620Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:30.212584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:42:30.611818Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:43:01.484304Z | Info | Live bytes: 1091.92MB Heap size: 3084.91MB +2024-07-16T06:43:05.814053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:06.500566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:07.309630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:43:07.782197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:08.361452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:10.312461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:11.107313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:12.189153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:12.868570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:14.038359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:14.853776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:42.569934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:45.916554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:46.808418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:47.515391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:43:58.291303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:44:01.487624Z | Info | Live bytes: 1128.98MB Heap size: 3084.91MB +2024-07-16T06:44:04.176668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:44:12.781445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:44:14.930758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:44:57.678066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:44:58.401090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:01.492203Z | Info | Live bytes: 1144.03MB Heap size: 3084.91MB +2024-07-16T06:45:09.454579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:13.794661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:17.081874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:17.386777Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:45:29.868895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:30.457314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:36.445954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:37.898956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:38.475452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:42.127732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:45.264383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:45:45.418803Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:45:45.480123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:46.102225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:45:46.752421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:01.494980Z | Info | Live bytes: 878.09MB Heap size: 3230.66MB +2024-07-16T06:46:04.498182Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:04.536383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:04.792473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:05.292532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:06.387579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:07.952086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:08.325407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:11.802613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:13.300712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:13.826424Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:46:17.697519Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:46:29.422052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:30.032613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:34.318053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:34.468817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:34.506628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:34.607111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:34.687074Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:35.020062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:35.101766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:35.385184Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:35.772251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:35.875100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:35.901594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:36.016235Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:36.433752Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:36.515111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:36.786582Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:37.147818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:37.305667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:37.694608Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:37.770434Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:37.896001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:38.216275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:38.857080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:44.077312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:46.731924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:47.153799Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:47.366471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:47.498804Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:46:47.951248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:49.500857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:57.356628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:59.188001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:46:59.791603Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:47:00.491576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:01.498037Z | Info | Live bytes: 1382.67MB Heap size: 3230.66MB +2024-07-16T06:47:12.557280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:29.775286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:30.132020Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:47:30.474769Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:47:30.658298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:30.921363Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:47:31.052818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T06:47:31.461565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:32.716495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:33.470149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:33.711020Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T06:47:34.405299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T06:47:46.736257Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T06:48:01.505857Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:49:01.525106Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:50:01.586286Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:51:01.641684Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:52:01.701581Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:53:01.719577Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:54:01.779556Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:55:01.835392Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:56:01.877620Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:57:01.938521Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:58:01.999378Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T06:59:02.017710Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:00:02.046612Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:01:02.098510Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:02:02.158541Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:03:02.218611Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:04:02.257188Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:05:02.270193Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:06:02.275971Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:07:02.336525Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:08:02.347540Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:09:02.407518Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:10:02.434040Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:11:02.489492Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:12:02.525523Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:13:02.586404Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:14:02.647289Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:15:02.708369Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:16:02.769394Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:17:02.829771Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:18:02.891031Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:19:02.952563Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:20:03.001882Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:21:03.026616Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:22:03.088060Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:23:03.149069Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:24:03.210559Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:25:03.271946Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:26:03.333845Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:27:03.395108Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:28:03.456099Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:29:03.475780Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:30:03.493893Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:31:03.540507Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:32:03.600775Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:33:03.625726Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:34:03.657606Z | Info | Live bytes: 1000.73MB Heap size: 3230.66MB +2024-07-16T07:35:03.718506Z | Info | Live bytes: 1012.14MB Heap size: 3230.66MB +2024-07-16T07:35:11.924894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:35:14.042360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:35:14.693644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:01.211851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:02.979421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:03.097728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:03.215404Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:03.555487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:03.721824Z | Info | Live bytes: 1029.37MB Heap size: 3230.66MB +2024-07-16T07:36:04.570638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:05.348814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:08.269940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:08.323961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:08.520313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:08.636012Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:08.654193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:09.931171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:12.012419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:20.703289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:21.276324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:21.610294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:22.073923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:22.206928Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:22.712228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:24.412155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:27.214023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:27.985051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:28.004862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:29.839965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:30.663430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:30.696003Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:30.807916Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:31.301607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:42.785260Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:42.924369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:42.964913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:43.105628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:43.357149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:43.486531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:43.572598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:43.593323Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:43.703575Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:43.848917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:43.971184Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:44.094221Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:44.152043Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:44.221142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:44.306594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:36:44.823745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:45.426669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:46.032279Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T07:36:46.729337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:52.248900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:36:52.820718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:37:03.728891Z | Info | Live bytes: 1240.72MB Heap size: 3230.66MB +2024-07-16T07:37:07.431287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:37:21.884046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:37:22.984396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:37:23.990118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:37:59.519095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:00.060439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:00.171112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:00.247165Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:00.804319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:01.850695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:02.452402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:03.168911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:03.190314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:03.273403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:03.730177Z | Info | Live bytes: 1280.00MB Heap size: 3230.66MB +2024-07-16T07:38:03.769666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:10.612987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:12.018847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:12.297519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:12.366325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:12.732705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:14.116642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:14.695309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:15.569576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:16.234877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:17.878314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:18.488537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:21.446562Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:21.747727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:22.011288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:22.167848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:38:22.417269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:23.055840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:38:23.177169Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T07:39:03.771680Z | Info | Live bytes: 1358.55MB Heap size: 3230.66MB +2024-07-16T07:39:24.186875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:36.081626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:37.701096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:39.298435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:40.654651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:40.699831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:39:40.753315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:39:41.310056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:42.276214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:42.874179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:39:50.367814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:03.781059Z | Info | Live bytes: 1399.35MB Heap size: 3230.66MB +2024-07-16T07:40:26.710075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:33.794277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:34.533075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:36.257067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:37.124938Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:40:37.159795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:40:37.545982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:38.386938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:39.209385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:40.795429Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:40:41.062334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:40:41.263606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:41.759129Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:40:42.334536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:40:42.767648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:43.232121Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:40:44.138161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:40:57.065473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:41:03.783716Z | Info | Live bytes: 1443.02MB Heap size: 3230.66MB +2024-07-16T07:42:03.790409Z | Info | Live bytes: 1443.02MB Heap size: 3230.66MB +2024-07-16T07:43:03.848244Z | Info | Live bytes: 1443.02MB Heap size: 3230.66MB +2024-07-16T07:44:03.889732Z | Info | Live bytes: 1443.02MB Heap size: 3230.66MB +2024-07-16T07:44:19.085035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:44:19.261395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:20.182634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:20.198243Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:44:20.257051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:44:20.816680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:21.472197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:22.825514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:24.365386Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:25.932731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:26.917877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:50.024436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:51.027192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:52.593563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:53.177183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:44:53.204537Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:44:53.336759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:54.070436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:54.450262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:44:54.927091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:44:55.625298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:01.838834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:02.454967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:03.027016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:03.890838Z | Info | Live bytes: 818.85MB Heap size: 3230.66MB +2024-07-16T07:45:04.343151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:05.184536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:06.449047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:06.481424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:45:07.070968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:08.468384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:09.470550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:10.056492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:11.113827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:14.593457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:45:14.631953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:23.032825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:23.647648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:25.860142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:27.573091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:28.491541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:29.261632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:45:40.751701Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:46:03.909714Z | Info | Live bytes: 947.78MB Heap size: 3230.66MB +2024-07-16T07:46:20.088225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:01.993619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:03.913014Z | Info | Live bytes: 976.70MB Heap size: 3230.66MB +2024-07-16T07:47:04.370318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:07.156312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:07.900596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:34.629793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:42.123071Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:47:42.296575Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:48.377793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:47:48.549722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:48.738256Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:47:48.838858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:47:49.155210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:53.363748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:53.958113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:54.580427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:55.991393Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:57.513712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:58.142819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:47:59.035787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:48:00.844624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:48:01.488657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:48:03.916570Z | Info | Live bytes: 1084.74MB Heap size: 3230.66MB +2024-07-16T07:48:07.612395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:48:07.879915Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T07:48:54.192747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:48:56.280419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:49:01.916934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:49:03.919553Z | Info | Live bytes: 1107.79MB Heap size: 3230.66MB +2024-07-16T07:49:11.462907Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:49:11.638771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:49:11.783998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:49:12.965267Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:49:13.343625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:49:21.449952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:49:37.918271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:49:41.662350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:49:58.870063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:50:01.050971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:50:03.922552Z | Info | Live bytes: 1198.81MB Heap size: 3230.66MB +2024-07-16T07:50:08.166639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:50:12.852057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:50:14.457801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:50:35.461894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:51:03.947096Z | Info | Live bytes: 1215.66MB Heap size: 3230.66MB +2024-07-16T07:52:04.008186Z | Info | Live bytes: 1215.66MB Heap size: 3230.66MB +2024-07-16T07:53:04.069232Z | Info | Live bytes: 1215.66MB Heap size: 3230.66MB +2024-07-16T07:54:04.129949Z | Info | Live bytes: 1215.66MB Heap size: 3230.66MB +2024-07-16T07:55:04.190682Z | Info | Live bytes: 1215.66MB Heap size: 3230.66MB +2024-07-16T07:56:04.211741Z | Info | Live bytes: 1215.66MB Heap size: 3230.66MB +2024-07-16T07:56:09.334686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:10.865006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:11.845795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:56:11.944137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:12.419586Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:56:12.977000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:13.652409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:14.394677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:15.134406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:18.611222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:56:20.125287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:04.246329Z | Info | Live bytes: 1305.38MB Heap size: 3230.66MB +2024-07-16T07:57:08.337084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:09.252824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:14.720504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:15.480891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:19.180454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:20.216535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:22.180334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:22.416114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:22.617706Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:22.838416Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:22.842884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:23.767478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:24.197126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:24.975204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:25.862607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:26.122882Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:26.472907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:33.318578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:39.912853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:39.978860Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:40.092403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:40.199161Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T07:57:40.686528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:57:41.087052Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T07:57:41.272621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:58:04.254637Z | Info | Live bytes: 898.21MB Heap size: 3230.66MB +2024-07-16T07:58:20.258776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T07:59:04.298525Z | Info | Live bytes: 937.24MB Heap size: 3230.66MB +2024-07-16T08:00:04.359498Z | Info | Live bytes: 937.24MB Heap size: 3230.66MB +2024-07-16T08:01:04.419429Z | Info | Live bytes: 946.90MB Heap size: 3230.66MB +2024-07-16T08:01:59.441650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:02:04.421175Z | Info | Live bytes: 1012.56MB Heap size: 3230.66MB +2024-07-16T08:03:04.481583Z | Info | Live bytes: 1021.16MB Heap size: 3230.66MB +2024-07-16T08:04:04.542334Z | Info | Live bytes: 1021.16MB Heap size: 3230.66MB +2024-07-16T08:05:04.586303Z | Info | Live bytes: 1021.16MB Heap size: 3230.66MB +2024-07-16T08:06:04.591985Z | Info | Live bytes: 1021.16MB Heap size: 3230.66MB +2024-07-16T08:07:04.652609Z | Info | Live bytes: 1021.16MB Heap size: 3230.66MB +2024-07-16T08:08:04.713298Z | Info | Live bytes: 1021.16MB Heap size: 3230.66MB +2024-07-16T08:09:04.774215Z | Info | Live bytes: 1021.16MB Heap size: 3230.66MB +2024-07-16T08:09:29.558879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:30.177191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:31.029527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:31.763853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:32.987226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:34.036101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:34.759571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:36.142741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:40.754493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:42.270190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:58.238686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:58.972941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:09:59.592652Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:10:04.355452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:10:04.776471Z | Info | Live bytes: 1137.99MB Heap size: 3230.66MB +2024-07-16T08:10:05.935137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:10:14.180632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:11:04.817480Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:12:04.877653Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:13:04.937628Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:14:04.998655Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:15:05.031709Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:16:05.054147Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:17:05.115362Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:18:05.140547Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:19:05.196566Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:20:05.257646Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:21:05.282011Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:22:05.342979Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:23:05.369599Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:24:05.396219Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:25:05.456605Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:26:05.517354Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:27:05.578180Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:28:05.639113Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:29:05.665940Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:30:05.676527Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:31:05.737239Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:32:05.797606Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:33:05.857722Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:34:05.918529Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:35:05.936980Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:36:05.997971Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:37:06.058933Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:38:06.120025Z | Info | Live bytes: 1174.89MB Heap size: 3230.66MB +2024-07-16T08:39:06.126977Z | Info | Live bytes: 1177.04MB Heap size: 3230.66MB +2024-07-16T08:39:17.072054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:17.745310Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:17.882040Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:17.919944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:20.347169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:21.000067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:21.657330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:24.657768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:25.295354Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:25.712739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:25.742248Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:25.895196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:26.173078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:26.391411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:26.466144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:27.036751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:27.617835Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:27.631111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:27.881806Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:28.184408Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:28.373931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:28.716620Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:29.206822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:29.787412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:29.945374Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:30.082413Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:30.263452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:30.886558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:31.451484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:32.808392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:33.627231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:33.833078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:34.101685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:34.313636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:34.386206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:35.182076Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:35.299089Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:35.674855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:36.240444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:36.863272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:37.160529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:37.308797Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:37.647262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:39:39.217410Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:39.355230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:39.489011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:39.629438Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:39.758800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:39:41.042876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:40:06.148758Z | Info | Live bytes: 1364.77MB Heap size: 3230.66MB +2024-07-16T08:41:06.209669Z | Info | Live bytes: 1364.77MB Heap size: 3230.66MB +2024-07-16T08:41:17.215412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:41:19.461534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:42:06.219365Z | Info | Live bytes: 1404.09MB Heap size: 3230.66MB +2024-07-16T08:43:06.279942Z | Info | Live bytes: 1404.09MB Heap size: 3230.66MB +2024-07-16T08:44:06.291435Z | Info | Live bytes: 1404.09MB Heap size: 3230.66MB +2024-07-16T08:45:06.352260Z | Info | Live bytes: 1404.09MB Heap size: 3230.66MB +2024-07-16T08:46:06.395915Z | Info | Live bytes: 1404.09MB Heap size: 3230.66MB +2024-07-16T08:47:06.407378Z | Info | Live bytes: 1404.09MB Heap size: 3230.66MB +2024-07-16T08:47:31.277771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:47:32.140917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:47:33.461165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:47:34.879376Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:47:34.960554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:47:35.322969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:47:35.956764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:47:36.898794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:47:37.923605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:47:46.136394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:48:06.423556Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:49:06.484461Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:50:06.542882Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:51:06.603776Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:52:06.611458Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:53:06.672804Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:54:06.707576Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:55:06.712661Z | Info | Live bytes: 786.90MB Heap size: 3230.66MB +2024-07-16T08:56:06.773657Z | Info | Live bytes: 786.87MB Heap size: 3230.66MB +2024-07-16T08:57:06.834519Z | Info | Live bytes: 786.87MB Heap size: 3230.66MB +2024-07-16T08:58:04.196142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:05.828562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:06.001234Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:06.027951Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:06.406384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:06.836802Z | Info | Live bytes: 826.44MB Heap size: 3230.66MB +2024-07-16T08:58:07.404320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:08.386310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:09.979589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:10.100505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:10.298131Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:10.588837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:11.585961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:11.695520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:11.795477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:11.950241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:12.603418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:14.693527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:19.611603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:19.754619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:20.044826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:58:20.191381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:21.214399Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:40.646620Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:41.413845Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:42.073609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:42.694225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:43.419954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:44.012541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:58:59.887761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:06.839602Z | Info | Live bytes: 949.20MB Heap size: 3230.66MB +2024-07-16T08:59:08.822565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:17.735640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:18.453433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:19.206510Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T08:59:19.920499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:32.417781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:40.175686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:40.775634Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:40.902433Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:41.187812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:42.244705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:42.954863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:44.100748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:44.689080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:45.686687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:46.357152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:47.016107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:47.896236Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:48.124458Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:48.305233Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:48.341104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:49.224668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:49.436075Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:49.691420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:50.044650Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T08:59:50.407311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T08:59:55.439290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:01.728477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:06.841491Z | Info | Live bytes: 1092.41MB Heap size: 3230.66MB +2024-07-16T09:00:23.659046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:30.837105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:34.218664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:34.783471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:35.450456Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:38.865397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:43.700969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:46.068491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:00:53.293165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:01:05.106742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:01:06.843686Z | Info | Live bytes: 1232.79MB Heap size: 3230.66MB +2024-07-16T09:02:06.787418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:02:06.852118Z | Info | Live bytes: 1243.32MB Heap size: 3230.66MB +2024-07-16T09:02:18.942463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:02:31.684274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:02:32.249315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:02:33.176736Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:03:03.984564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:05.396148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:06.855396Z | Info | Live bytes: 1298.41MB Heap size: 3230.66MB +2024-07-16T09:03:19.966835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:27.648626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:28.414982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:28.817049Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:28.998501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:29.032488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:30.108578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:30.274131Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:30.772073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:31.050667Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:31.215027Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:31.364013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:32.968995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:33.708375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:35.075005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:35.954504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:36.568669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:41.417031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:45.599662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:46.614961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:47.005110Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:47.064050Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:47.252928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:47.905514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:49.411818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:49.986022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:03:50.159218Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:03:50.652931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:06.864548Z | Info | Live bytes: 1462.90MB Heap size: 3230.66MB +2024-07-16T09:04:08.145703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:26.391019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:27.553756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:28.296843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:29.406714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:30.175494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:40.335960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:56.703298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:57.868810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:04:59.930121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:05:00.772216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:05:06.865521Z | Info | Live bytes: 1013.63MB Heap size: 3240.10MB +2024-07-16T09:05:12.130464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:05:12.784211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:05:19.856162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:05:22.981294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:05:23.616847Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:06:06.909002Z | Info | Live bytes: 1087.01MB Heap size: 3240.10MB +2024-07-16T09:06:51.469596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:06.473947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:06.910067Z | Info | Live bytes: 1091.76MB Heap size: 3240.10MB +2024-07-16T09:07:07.068740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:07.719423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:08.324217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:09.485049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:10.119372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:10.757007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:12.565093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:14.402378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:30.350260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:32.171610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:32.884003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:34.077729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:34.871031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:35.456855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:36.196789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:40.752538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:41.515590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:41.840186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:07:42.144335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:07:42.239420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:52.733475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:53.785250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:58.036504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:07:59.458989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:00.596930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:02.124155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:04.001561Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:04.098445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:04.372452Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:04.810105Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:04.867792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:06.011817Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:06.167114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:06.577296Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:06.913439Z | Info | Live bytes: 1458.63MB Heap size: 3240.10MB +2024-07-16T09:08:07.533955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:09.596557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:12.295431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:15.201418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:15.355984Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:15.485634Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:16.044382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:17.335302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:17.451488Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:17.947616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:18.493484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:08:18.994370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:19.738594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:20.414482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:21.306860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:23.021936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:08:23.225332Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:08:23.969497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:09:06.924642Z | Info | Live bytes: 1138.51MB Heap size: 3275.75MB +2024-07-16T09:09:10.504306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:09:11.079102Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:10:06.975632Z | Info | Live bytes: 1291.48MB Heap size: 3275.75MB +2024-07-16T09:10:40.928276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:42.229634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:42.928243Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:10:43.030766Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:10:43.136134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:43.152264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:10:43.256813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:10:43.772702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:44.777195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:46.669755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:51.184795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:10:51.270384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:10:51.367560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:52.403178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:53.056432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:53.727133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:54.359976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:10:56.003979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:03.368385Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:11:03.696840Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:11:03.861855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:03.883818Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:11:04.089190Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:11:04.601379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:06.979669Z | Info | Live bytes: 1382.73MB Heap size: 3275.75MB +2024-07-16T09:11:33.186052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:34.262219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:37.331900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:43.765016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:48.690181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:50.276710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:50.871460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:51.543567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:52.233700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:52.819980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:11:57.138651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:06.576761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:06.980511Z | Info | Live bytes: 1392.44MB Heap size: 3275.75MB +2024-07-16T09:12:12.574072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:17.118044Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:17.272288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:17.350230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:17.412381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:17.469257Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:17.540233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:18.083293Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:12:18.327505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:21.275008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:21.761602Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:21.923061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:22.017736Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:22.120145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:23.747490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:24.450780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:25.026712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:25.648420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:26.621530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:32.937419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:33.552987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:33.956468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:12:34.423375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:35.426758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:37.301235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:38.927510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:45.673848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:47.565859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:48.192133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:48.799239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:49.434309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:12:49.608036Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:13:01.711494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:03.489997Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:03.756741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:03.952602Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:04.010366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:04.249472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:04.790945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:05.086115Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:13:05.785895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:06.981539Z | Info | Live bytes: 964.73MB Heap size: 3389.00MB +2024-07-16T09:13:28.703023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:29.071733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:29.202788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:29.480656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:31.236149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:31.331605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:31.705521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:32.253393Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:32.356933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:32.381995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:32.584605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:32.993693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:33.227498Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:33.333681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:33.626767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:36.866503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:52.304830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:52.993424Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:55.062479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:55.287714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:55.421547Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:55.627821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:55.768803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:13:56.319661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:13:56.475881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:14:06.983465Z | Info | Live bytes: 1126.52MB Heap size: 3389.00MB +2024-07-16T09:14:23.843489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:14:24.603687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:14:55.515004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:14:57.418197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:00.630096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:06.986598Z | Info | Live bytes: 1170.99MB Heap size: 3389.00MB +2024-07-16T09:15:10.427454Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:10.877357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:13.066867Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:13.441607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:13.532704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:21.316610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:22.273356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:24.142201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:24.638013Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:25.039764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:26.557376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:27.174167Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:27.270885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:27.335358Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:27.689849Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:27.864569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:27.958011Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:28.119071Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:28.176283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:28.310763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:28.597668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:28.677587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:28.793679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:29.809940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:30.903441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:31.891213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:31.987554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:32.008034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:33.961606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:34.329913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:38.664432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:42.721114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:43.634858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:44.085376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:44.322183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:44.728573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:45.328889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:45.976078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:46.698094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:47.109392Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:47.283939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:47.965689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:48.631297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:49.489800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:50.295599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:52.167436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:52.844182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:53.766564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:54.404614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:55.406101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:56.187233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:57.438277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:58.054503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:58.713192Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:58.770284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:15:59.067674Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:15:59.555668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:00.157029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:00.859459Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:16:00.921486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:01.103282Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:16:01.214823Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:16:01.334698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:16:01.419848Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:16:01.516881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:01.589616Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:16:06.987862Z | Info | Live bytes: 1484.88MB Heap size: 3389.00MB +2024-07-16T09:16:08.470631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:14.504223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:16.851201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:18.870971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:20.816949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:23.478514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:24.896375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:52.148877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:57.975498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:16:59.315772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:02.217637Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:06.993566Z | Info | Live bytes: 1575.78MB Heap size: 3389.00MB +2024-07-16T09:17:16.425806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:17.392747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:18.585053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:18.697371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:19.337209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:20.039940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:20.857300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:21.699246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:22.838673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:30.455190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:38.557288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:38.649549Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:38.727827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:38.799868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:38.866453Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.106988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.259976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.337749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.469605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:39.482198Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.625945Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.721168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.843606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:39.921903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:40.147672Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:40.878671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:41.202022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:41.324946Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:41.436618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:41.551061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:41.593612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:41.600517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:17:41.967112Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:17:42.599409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:17:50.098952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:18:06.995114Z | Info | Live bytes: 944.57MB Heap size: 3404.73MB +2024-07-16T09:18:07.325839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:18:07.937926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:18:22.501314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:18:25.553564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:18:26.276000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:18:48.169825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:18:48.998887Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T09:19:00.218143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:06.122575Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:07.002251Z | Info | Live bytes: 1330.80MB Heap size: 3404.73MB +2024-07-16T09:19:10.843500Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:19:10.961425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:19:11.049490Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:19:11.142318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:11.197454Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:19:11.773318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:12.574143Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:19:13.179900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:17.757055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:18.317944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:19.363887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:22.531077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:19:23.253712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:20:07.009393Z | Info | Live bytes: 873.45MB Heap size: 3404.73MB +2024-07-16T09:21:07.069533Z | Info | Live bytes: 873.45MB Heap size: 3404.73MB +2024-07-16T09:22:07.070400Z | Info | Live bytes: 860.96MB Heap size: 3404.73MB +2024-07-16T09:22:07.507977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:08.677210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:14.976739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:15.746951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:16.521080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:16.689800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:22:16.799501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:22:16.962855Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:22:17.177574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:17.219602Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:22:17.331699Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:22:17.453557Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:22:17.577637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T09:22:17.822017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:18.163917Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:22:18.861136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:20.727041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:20.776701Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:22:23.441956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T09:22:25.896501Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T09:23:07.094470Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:24:07.125104Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:25:07.186141Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:26:07.246912Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:27:07.307694Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:28:07.314929Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:29:07.375846Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:30:07.436476Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:31:07.477504Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:32:07.537560Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:33:07.549044Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:34:07.609524Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:35:07.653873Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:36:07.714513Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:37:07.774575Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:38:07.834527Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:39:07.839566Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:40:07.894535Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:41:07.954553Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:42:08.014585Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:43:08.074634Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:44:08.134602Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:45:08.194577Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:46:08.254887Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:47:08.314502Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:48:08.374489Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:49:08.434564Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:50:08.494571Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:51:08.554514Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:52:08.614499Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:53:08.635506Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:54:08.695599Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:55:08.755556Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:56:08.815578Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:57:08.837538Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:58:08.897460Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T09:59:08.957616Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:00:09.018334Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:01:09.079061Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:02:09.139650Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:03:09.200581Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:04:09.261599Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:05:09.305950Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:06:09.332014Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:07:09.393568Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:08:09.455256Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:09:09.516579Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:10:09.577744Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:11:09.639087Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:12:09.699714Z | Info | Live bytes: 897.73MB Heap size: 3404.73MB +2024-07-16T10:13:04.777822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:05.346508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:06.663572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:06.742870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:06.902919Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:06.997296Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:07.098637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:07.351094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:07.453010Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:07.947925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:08.623578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:09.702749Z | Info | Live bytes: 894.94MB Heap size: 3404.73MB +2024-07-16T10:13:10.385885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:14.359666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:15.729615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:16.712043Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:16.840736Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:17.125911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:26.971622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:28.750567Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:28.887065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:29.560987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:13:30.048044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:13:39.225126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:09.718506Z | Info | Live bytes: 993.77MB Heap size: 3404.73MB +2024-07-16T10:14:30.662870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:32.213222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:33.198002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:35.799183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:14:35.989355Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:14:36.255312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:38.237234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:38.485644Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:14:38.701453Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:14:38.958829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:44.427512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:45.113209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:45.814654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:46.403236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:14:46.973728Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:15:09.741990Z | Info | Live bytes: 1016.19MB Heap size: 3404.73MB +2024-07-16T10:16:09.803063Z | Info | Live bytes: 1016.19MB Heap size: 3404.73MB +2024-07-16T10:16:27.544705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:03.243290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:03.847853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:09.803520Z | Info | Live bytes: 1012.94MB Heap size: 3404.73MB +2024-07-16T10:17:20.259840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:24.444077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:25.088195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:25.575361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:25.645484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:25.866086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:26.235020Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:26.487759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:26.622055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:26.731823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:26.907718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:27.402031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:28.114760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:28.815773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:33.290889Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:34.292733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:34.531447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:34.645583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:34.945511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:35.603698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:35.715441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:17:36.076123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:40.067472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:53.574384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:17:53.874160Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-16T10:18:01.334930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:18:02.525157Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:18:05.879749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:18:06.517013Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:18:09.806963Z | Info | Live bytes: 1443.04MB Heap size: 3404.73MB +2024-07-16T10:18:51.368804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:18:52.133114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:18:54.601311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:18:54.671896Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:19:09.822500Z | Info | Live bytes: 1449.31MB Heap size: 3404.73MB +2024-07-16T10:19:14.734458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:16.176800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:17.943459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:18.583728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:22.790391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:34.447532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:36.142783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:41.403191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:43.113587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:43.590182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:46.196495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:46.552181Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:46.791441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:46.907583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:46.940580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:47.076922Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:47.443770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:47.562927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:47.704903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:47.941513Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:48.049313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:48.148520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:48.250863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:48.742590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:51.353826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:51.849556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:51.999612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:52.060124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:52.472028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:52.563235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:52.785259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:52.876330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:52.962675Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:53.263414Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:53.284031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:53.386471Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:53.464422Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:53.533239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:53.617910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:53.706079Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:53.808695Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:54.075627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:54.091191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:55.777030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:55.804229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:55.903066Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:56.390095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:19:57.068411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:57.148375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:19:57.564616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:09.830392Z | Info | Live bytes: 779.05MB Heap size: 3404.73MB +2024-07-16T10:20:19.585990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:20.174722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:28.607530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:29.382610Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:29.478084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:29.595487Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:29.711709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:30.285930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:40.978306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:43.276978Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:47.608213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:47.660737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:48.052379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:48.434628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:48.984779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:49.087260Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:49.914372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:52.227361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:52.800038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:53.751707Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:20:54.003501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:54.046933Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:20:54.751799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:59.277232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:20:59.649599Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:21:09.733019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:09.832812Z | Info | Live bytes: 1284.19MB Heap size: 3404.73MB +2024-07-16T10:21:11.583311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:25.231523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:28.100575Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:28.363382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:28.500918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:28.859237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:29.935101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:30.775959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:31.392796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:39.525796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:42.991537Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:43.060630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:43.099822Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:43.266682Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:43.342115Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:43.681223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:43.965722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:44.125599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:44.239693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:44.443698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:44.457232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:44.550046Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:44.615918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:44.725918Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:45.031715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:45.055439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:45.155019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:45.650125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:45.668860Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:45.815545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:46.231913Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:46.312678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:46.415860Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:46.512241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:46.704958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:46.813265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:46.909816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:47.548196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:50.380243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:51.440912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:52.447702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:53.174614Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:53.220275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:54.419150Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:21:54.800915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:21:59.375034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:22:02.142078Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:22:02.716709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:22:05.933614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:22:06.640709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:22:07.258597Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:22:09.835813Z | Info | Live bytes: 1366.13MB Heap size: 3404.73MB +2024-07-16T10:22:53.181325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:22:56.426611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:22:56.918124Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:23:05.288183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:23:06.555191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:23:09.839624Z | Info | Live bytes: 1358.14MB Heap size: 3404.73MB +2024-07-16T10:23:12.508551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:23:12.775668Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:23:21.513964Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:23:21.630952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:23:21.730270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:23:21.973409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:23:22.304920Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T10:24:09.852337Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:25:09.913748Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:26:09.975057Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:27:10.036251Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:28:10.097732Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:29:10.159537Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:30:10.221238Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:31:10.282488Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:32:10.343287Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:33:10.404705Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:34:10.466961Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:35:10.528563Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:36:10.537954Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:37:10.555528Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:38:10.616555Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:39:10.633132Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:40:10.694545Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:41:10.755821Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:42:10.817299Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:43:10.878722Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:44:10.881941Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:45:10.943414Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:46:10.953910Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:47:11.015476Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:48:11.077171Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:49:11.138704Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:50:11.200236Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:51:11.261747Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:52:11.321844Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:53:11.383475Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:54:11.444993Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:55:11.506571Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:56:11.551774Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:57:11.585819Z | Info | Live bytes: 1381.12MB Heap size: 3404.73MB +2024-07-16T10:58:11.588498Z | Info | Live bytes: 1376.33MB Heap size: 3404.73MB +2024-07-16T10:58:23.280096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:33.001818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:44.242317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:45.983353Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:46.133998Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:46.258402Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:46.389719Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:46.471326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:46.494397Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:46.654084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:46.828712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:46.944987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:47.135739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:47.153256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:47.719445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:51.221589Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:51.242146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:52.048244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:58:52.605249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:53.420243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:54.016317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:58:55.733099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:11.493132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:11.590147Z | Info | Live bytes: 1433.65MB Heap size: 3404.73MB +2024-07-16T10:59:12.120745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:13.575095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:13.674002Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:13.701387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:16.018064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:16.044098Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:16.905776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:17.854263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:18.594816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:19.368844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:19.431773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:19.502733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:19.783605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:19.960414Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:20.096571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:20.118372Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:20.253473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:20.357226Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T10:59:20.743535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:32.310757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:36.679409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:37.273854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:39.632453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T10:59:40.273238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:00:11.618484Z | Info | Live bytes: 1484.31MB Heap size: 3404.73MB +2024-07-16T11:00:41.429542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:00:45.601644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:00:47.653403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:47.831506Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:48.011391Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:48.125687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:00:48.251484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:48.438624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:48.725580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:00:48.754937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:49.207680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:49.692580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:00:50.455307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:50.807077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:00:50.927033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:00:56.806225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:11.628126Z | Info | Live bytes: 1494.36MB Heap size: 3404.73MB +2024-07-16T11:01:15.381043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:17.789633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:18.441541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:21.160403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:21.804085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:25.764239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:25.864319Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:25.937105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:25.970452Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:26.362821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:26.481401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:26.559324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:26.592743Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:26.685983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:26.851092Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:26.958418Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:27.052626Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:27.120544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:27.202573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:27.205138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:27.798921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:27.953454Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:28.217283Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:28.316244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:28.458364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:28.738222Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:28.954569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:29.083917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:29.160055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:29.268023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:29.293062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:29.316456Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:29.593050Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:29.685811Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:29.847129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:30.004660Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:30.100548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:30.386133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:30.538728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:31.095936Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:31.203785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:31.452176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:31.594279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:31.802382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:31.855517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:31.926899Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:01:32.054938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:32.310879Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:01:33.014269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:41.591731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:42.692758Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:01:44.449280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:45.390815Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:01:46.090840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:01:50.460788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:02.471949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:11.634295Z | Info | Live bytes: 978.69MB Heap size: 3404.73MB +2024-07-16T11:02:17.032018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:18.093183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:18.807981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:19.896756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:02:20.354640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:21.325483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:21.976580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:31.573224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:32.157207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:32.825527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:34.041627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:35.528232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:40.131869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:41.430212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:42.210413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:43.548551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:44.658010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:47.803299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:50.579909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:51.275041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:53.839150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:54.623975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:54.880260Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:02:55.577761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:02:59.653792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:05.171876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:07.119704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:07.764509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:08.449121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:09.117946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:11.121333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:11.636606Z | Info | Live bytes: 1053.52MB Heap size: 3404.73MB +2024-07-16T11:03:14.740104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:15.374401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:16.003450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:16.811785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:17.111575Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:03:17.819619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:34.593582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:35.296970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:37.501959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:38.325597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:38.992069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:39.603821Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:03:42.177702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:04:07.637330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:04:11.641686Z | Info | Live bytes: 1066.68MB Heap size: 3404.73MB +2024-07-16T11:05:11.669234Z | Info | Live bytes: 1066.68MB Heap size: 3404.73MB +2024-07-16T11:05:25.170710Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:05:25.360292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:05:25.518975Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:05:25.651663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:05:25.663367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:25.758479Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:05:25.836413Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:05:26.236868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:28.611896Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:05:38.511285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:40.269694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:40.945729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:42.864860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:47.011854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:48.035234Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:05:50.554446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:57.260037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:58.638195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:59.271465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:05:59.501120Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:06:00.195172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:05.832261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:06.226701Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:06:11.673161Z | Info | Live bytes: 1432.19MB Heap size: 3404.73MB +2024-07-16T11:06:14.400272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:15.479748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:22.306028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:23.238277Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:06:26.405094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:29.660121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:38.823444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:39.957947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:46.962888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:47.377001Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:06:53.075735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:54.481252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:55.527104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:56.255490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:58.507991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:06:59.498290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:00.341976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:01.275193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:02.470413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:03.324964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:04.900929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:05.218529Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:07:05.919841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:11.680088Z | Info | Live bytes: 1087.90MB Heap size: 3404.73MB +2024-07-16T11:07:22.138872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:22.285184Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:07:34.681706Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:07:34.765519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:07:34.845414Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:07:35.034733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:35.093017Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:07:35.298090Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:07:35.602447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:36.233903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:44.978087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:46.877478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:47.817123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:48.394532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:48.903771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:07:49.395047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:49.589144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:07:50.013776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:50.652639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:51.303652Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:52.081440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:52.954605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:53.576427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:57.088196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:58.100868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:58.695653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:07:59.280566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:08:00.875433Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:08:01.582221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:08:11.690199Z | Info | Live bytes: 1120.39MB Heap size: 3404.73MB +2024-07-16T11:09:11.752164Z | Info | Live bytes: 1120.39MB Heap size: 3404.73MB +2024-07-16T11:09:55.205366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:10:11.769427Z | Info | Live bytes: 1111.22MB Heap size: 3404.73MB +2024-07-16T11:10:44.677132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:10:54.709704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:10:55.601433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:07.189208Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:07.307026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:07.393037Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:07.434259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:07.507776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:08.003157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:08.011839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:08.158082Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:08.445082Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:08.708405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:08.741154Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:08.862397Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.022120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.094034Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.180215Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.287388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:09.366168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.661491Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.834483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.868021Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:09.906833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:10.080180Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:10.337247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:10.497512Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:10.620029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:10.813099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:10.841412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:11.382932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:11.540001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:11.642708Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:11.757961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:11.770385Z | Info | Live bytes: 1161.19MB Heap size: 3404.73MB +2024-07-16T11:11:11.869413Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:12.091691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:12.311979Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:12.461183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:12.616664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:12.862048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:13.131971Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:13.209652Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:13.312058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:13.360125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:13.646738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:13.995663Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:14.107530Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:14.292630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:14.539010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:14.823379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:15.359311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:15.418322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:15.512243Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:15.587459Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:15.949683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:16.143428Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:11:16.845674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:21.280795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:21.557382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:21.752875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:21.915866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:22.251223Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:22.352773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:22.417768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:22.915693Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:23.168099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:23.255183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:23.435287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:25.441055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:26.049269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:26.640833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:28.239745Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:28.648743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:28.778209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:28.872231Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:29.095411Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:29.193245Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:29.277358Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:29.325018Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:30.717006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:32.178173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:33.999676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:50.997062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:51.692951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:51.972814Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:52.130952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:52.353713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:52.458840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:52.475656Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:52.596183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:53.066169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:54.150802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:54.800331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:55.387003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:56.739514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:57.315042Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:57.480767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:57.644204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:57.739898Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:58.096196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:58.126709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:58.771909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:11:59.190829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:59.299550Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:11:59.674448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:00.279375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:00.554839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:12:01.027417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:01.823564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:11.776888Z | Info | Live bytes: 908.40MB Heap size: 3437.23MB +2024-07-16T11:12:37.312879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:38.849918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:39.709643Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:43.957698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:46.902388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:12:49.436003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:13:11.794699Z | Info | Live bytes: 965.06MB Heap size: 3437.23MB +2024-07-16T11:14:11.834013Z | Info | Live bytes: 965.06MB Heap size: 3437.23MB +2024-07-16T11:15:11.865883Z | Info | Live bytes: 965.06MB Heap size: 3437.23MB +2024-07-16T11:15:50.122901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:50.585694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:15:50.703381Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:15:50.965073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:51.016069Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:15:51.109278Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:15:51.378510Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:15:51.544214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:15:51.589602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:52.190836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:52.839627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:53.689465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:54.718387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:55.833950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:57.239819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:58.462819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:59.186468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:15:59.785146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:01.077130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:04.098910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:04.505087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:10.753372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:11.867870Z | Info | Live bytes: 947.60MB Heap size: 3437.23MB +2024-07-16T11:16:26.479850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:27.223797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:35.826741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:35.870224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:36.222926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:36.941585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:37.584850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:38.302289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:38.311444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:45.968226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:46.602635Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:46.674824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:46.717315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:46.848423Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:47.322658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:47.518987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:47.754357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:16:47.995176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:49.066758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:16:54.847247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:11.881905Z | Info | Live bytes: 994.11MB Heap size: 3437.23MB +2024-07-16T11:17:14.530817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:15.193004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:15.214219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:17:15.972285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:17.042273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:18.086068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:18.963670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:19.368572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:17:19.522357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:17:19.565892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:20.227599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:20.879118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:21.656141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:22.319747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:17:22.336604Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:17:22.431096Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:17:22.917110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:11.925306Z | Info | Live bytes: 1161.18MB Heap size: 3437.23MB +2024-07-16T11:18:24.518238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:26.316840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:26.901388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:27.757453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:28.508514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:29.107733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:33.648915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:37.011466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:38.496806Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:18:39.195544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:47.034781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:50.473322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:55.543365Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:58.891903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:18:58.998588Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:18:59.086947Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:18:59.111935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:59.217286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:18:59.553559Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:18:59.666302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:18:59.701864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:18:59.775930Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:18:59.866669Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.027077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.127330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.232890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.285039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:00.329637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.450388Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.827010Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.905477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.952796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:00.969587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:01.041744Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:01.381947Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:01.563861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:01.582588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:01.622329Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:01.906199Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:02.162854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:02.260335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:02.334508Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:02.668852Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:19:02.787275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:03.414118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:08.823823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:11.926642Z | Info | Live bytes: 1578.39MB Heap size: 3437.23MB +2024-07-16T11:19:28.440010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:36.683549Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:37.047827Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:37.983688Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:38.447058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:41.568066Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:41.745516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:42.040037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:45.591224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:46.292456Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:46.746657Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:46.828952Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:46.944634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:46.961467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:47.166925Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:47.650840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:48.343794Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:48.427331Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:48.487559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:48.659872Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:48.837081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:48.929326Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:49.039095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:19:49.064509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:49.954700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:50.521317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:52.882719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:56.305551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:56.931120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:19:57.919022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:02.966578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:03.698983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:11.930945Z | Info | Live bytes: 1628.36MB Heap size: 3437.23MB +2024-07-16T11:20:12.909859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:13.840154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:18.422307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:20.526113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:20.981999Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:20:47.306975Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:20:47.505760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:47.520086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:20:47.638788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T11:20:48.132409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:48.801394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:20:53.603731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:00.584073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:01.279379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:03.920576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:07.852853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:11.936207Z | Info | Live bytes: 804.84MB Heap size: 3497.00MB +2024-07-16T11:21:16.454696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:21.746510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:22.402178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:25.243682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:26.016388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:28.750013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:29.326559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:21:30.020892Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:21:30.722176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:22:05.154315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:22:06.647733Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:22:11.942548Z | Info | Live bytes: 845.21MB Heap size: 3497.00MB +2024-07-16T11:23:11.950522Z | Info | Live bytes: 845.21MB Heap size: 3497.00MB +2024-07-16T11:23:28.616666Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs": [ ] +2024-07-16T11:23:28.970040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:24:11.977594Z | Info | Live bytes: 1008.74MB Heap size: 3497.00MB +2024-07-16T11:24:26.454495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T11:25:12.023045Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:26:12.084734Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:27:12.140058Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:28:12.201545Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:29:12.261558Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:30:12.310521Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:31:12.360861Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:32:12.422150Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:33:12.441910Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:34:12.496393Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:35:12.556750Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:36:12.617863Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:37:12.679216Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:38:12.740612Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:39:12.802019Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:40:12.863416Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:41:12.924670Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:42:12.985921Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:43:13.047232Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:44:13.106995Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:45:13.168228Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:46:13.229528Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:47:13.290832Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:48:13.352212Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:49:13.413706Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:50:13.455698Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:51:13.516958Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:52:13.526076Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:53:13.569851Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:54:13.585724Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:55:13.613436Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:56:13.626059Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:57:13.687246Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:58:13.748105Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T11:59:13.793853Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:00:13.817852Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:01:13.849864Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:02:13.865895Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:03:13.927216Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:04:13.945861Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:05:14.007189Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:06:14.068404Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:07:14.128741Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:08:14.189816Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:09:14.250978Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:10:14.297495Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:11:14.358720Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:12:14.420016Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:13:14.473848Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:14:14.535125Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:15:14.596483Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:16:14.657725Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:17:14.718914Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:18:14.780114Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:19:14.841475Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:20:14.902731Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:21:14.964020Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:22:14.969800Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:23:15.031028Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:24:15.092300Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:25:15.153274Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:26:15.168792Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:27:15.209241Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:28:15.270444Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:29:15.331528Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:30:15.353706Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:31:15.414902Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:32:15.476239Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:33:15.537552Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:34:15.545888Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:35:15.561872Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:36:15.569836Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:37:15.619324Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:38:15.667383Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:39:15.728679Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:40:15.733269Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:41:15.794520Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:42:15.824818Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:43:15.833884Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:44:15.895209Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:45:15.956541Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:46:16.002714Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:47:16.063642Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:48:16.124859Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:49:16.186208Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:50:16.211698Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:51:16.272908Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:52:16.334109Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:53:16.361264Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:54:16.422600Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:55:16.483900Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:56:16.545520Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:57:16.586508Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:58:16.596721Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T12:59:16.658230Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:00:16.697917Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:01:16.729969Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:02:16.783463Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:03:16.844849Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:04:16.906475Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:05:16.968017Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:06:17.001964Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:07:17.063539Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:08:17.125047Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:09:17.186567Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:10:17.188552Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:11:17.246555Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:12:17.307110Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:13:17.368153Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:14:17.428539Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:15:17.488543Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:16:17.549261Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:17:17.581164Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:18:17.642101Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:19:17.703298Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:20:17.727526Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:21:17.788205Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:22:17.790626Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:23:17.851658Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:24:17.912643Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:25:17.974326Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:26:18.035687Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:27:18.096981Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:28:18.158448Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:29:18.219890Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:30:18.261550Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:31:18.322697Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:32:18.384670Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:33:18.446186Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:34:18.507895Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:35:18.568562Z | Info | Live bytes: 1031.30MB Heap size: 3497.00MB +2024-07-16T13:35:20.224875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:35:20.998125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:35:36.437676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:35:37.808819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:15.243777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:36:15.387190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:15.391822Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:36:15.576245Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:36:15.969197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:16.493690Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:36:16.653670Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:36:17.195139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:18.569916Z | Info | Live bytes: 1104.70MB Heap size: 3497.00MB +2024-07-16T13:36:19.231767Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:36:19.296073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:36:19.793292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:24.204265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:24.935129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:26.316588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:36:59.364815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:37:00.581021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:37:00.632737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:37:09.915325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:37:14.870275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:37:18.573647Z | Info | Live bytes: 1400.69MB Heap size: 3497.00MB +2024-07-16T13:37:48.984996Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:37:55.386968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:38:18.592640Z | Info | Live bytes: 1394.38MB Heap size: 3497.00MB +2024-07-16T13:38:27.918734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:38:29.684713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:38:35.718146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:38:41.589480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:38:42.570501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:38:44.126539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:38:44.550655Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:38:45.283041Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:39:18.595213Z | Info | Live bytes: 1392.70MB Heap size: 3497.00MB +2024-07-16T13:40:18.656261Z | Info | Live bytes: 1392.70MB Heap size: 3497.00MB +2024-07-16T13:40:59.519017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:03.214084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:03.848372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:04.989778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:05.900173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:07.882412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:10.083891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:12.179335Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:16.530424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:16.682382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:16.757171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:16.798757Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:16.912644Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:17.157774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:17.404218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:17.571717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:17.712624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:18.052647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:18.222943Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:18.347261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:18.508614Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:18.657553Z | Info | Live bytes: 1405.53MB Heap size: 3497.00MB +2024-07-16T13:41:18.743988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:20.033552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:20.855253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:23.197344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:24.199630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:24.718132Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:24.824571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:24.909449Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:25.093396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:25.481651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:25.576527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:25.634986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:25.855827Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:26.127982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:26.493628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:26.584607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:26.823219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:26.921353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:27.180080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:27.295307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:27.413691Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:27.698244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:27.735614Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:27.837293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:27.949751Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:41:28.317073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:28.536493Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:28.732629Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:29.282108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:30.953122Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:30.970947Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:31.020931Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:32.951271Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-16T13:41:33.504912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:36.194872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:37.883914Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:38.344063Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:38.366841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:40.983100Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:41.423003Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:41.534252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:41.598394Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:41.742399Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:42.146950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:42.505173Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:42.842227Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:43.057332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:43.674469Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:41:44.226741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:49.433102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:50.735222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:41:55.744500Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-16T13:41:56.606628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:42:18.678880Z | Info | Live bytes: 1355.11MB Heap size: 3497.00MB +2024-07-16T13:42:36.588375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:43:18.704442Z | Info | Live bytes: 1368.01MB Heap size: 3497.00MB +2024-07-16T13:43:45.207749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:43:49.071922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:43:55.722143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:44:18.727852Z | Info | Live bytes: 1378.90MB Heap size: 3497.00MB +2024-07-16T13:45:18.767706Z | Info | Live bytes: 1378.90MB Heap size: 3497.00MB +2024-07-16T13:45:28.667718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:46:18.818049Z | Info | Live bytes: 1378.90MB Heap size: 3497.00MB +2024-07-16T13:46:36.873605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:46:37.113581Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:46:59.199569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:47:00.250084Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:47:07.979726Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:47:08.669794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:47:18.830415Z | Info | Live bytes: 1394.97MB Heap size: 3497.00MB +2024-07-16T13:47:28.601903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:47:28.822231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:47:28.965944Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:47:29.426507Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:47:29.484091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:47:30.149574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:47:32.947143Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:47:36.926432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:18.861582Z | Info | Live bytes: 1471.04MB Heap size: 3497.00MB +2024-07-16T13:48:26.540776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:27.640625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:31.826495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:33.316090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:38.193796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:48:38.242295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:38.279966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:48:38.392604Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:48:38.480843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:48:38.605799Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:48:38.885744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:38.971052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-16T13:48:39.451000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:41.407499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:43.531449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:44.414853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:51.038235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:51.783265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:57.091188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:57.712859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:58.284913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:48:58.871162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:49:02.608544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:49:03.366634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:49:07.450187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:49:10.717783Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:49:11.601464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:49:18.869583Z | Info | Live bytes: 1561.94MB Heap size: 3497.00MB +2024-07-16T13:49:27.691227Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-16T13:49:29.590733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:50:18.918055Z | Info | Live bytes: 1566.91MB Heap size: 3497.00MB +2024-07-16T13:50:25.100577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:50:39.608533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:50:41.371067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:01.147636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:01.872092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:02.814321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:03.574977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:04.210305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:05.258749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:06.009459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:06.994578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:07.631839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:08.381064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:08.963184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:09.537207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:10.455378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:11.485741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:13.080974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:13.652088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:14.683003Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/UnsignedTx.hs" ] +2024-07-16T13:51:15.483118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:17.635566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:18.439390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:18.919951Z | Info | Live bytes: 1625.32MB Heap size: 3497.00MB +2024-07-16T13:51:21.432651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:22.159058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:23.118794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:23.961225Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-16T13:51:24.815151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:42.678602Z | Info | LSP: received shutdown +2024-07-16T13:51:42.683550Z | Error | Got EOF +2024-07-16T13:51:56.525288Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-16T13:51:56.526320Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-16T13:51:56.526653Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-16T13:51:56.529054Z | Info | Logging heap statistics every 60.00s +2024-07-16T13:51:56.535722Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-16T13:51:56.536135Z | Info | Starting server +2024-07-16T13:51:56.538071Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-16T13:51:56.597441Z | Info | Started LSP server in 0.06s +2024-07-16T13:51:58.083885Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Eras.hs +2024-07-16T13:51:58.085567Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-16T13:51:58.704795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:58.704921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:51:59.950842Z | Info | Load cabal cradle using single file +2024-07-16T13:52:01.212883Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT374203-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-16T13:52:09.460517Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-91ce7db861ce9f8a5fa5cdd35181cbff88842a76 +2024-07-16T13:52:09.471531Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-16T13:52:56.562596Z | Info | Live bytes: 826.96MB Heap size: 2113.93MB +2024-07-16T13:53:10.126185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:53:11.810563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:53:12.563763Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-16T13:53:12.701241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:53:13.270042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:53:56.584250Z | Info | Live bytes: 941.79MB Heap size: 2177.89MB +2024-07-16T13:54:56.591328Z | Info | Live bytes: 941.79MB Heap size: 2177.89MB +2024-07-16T13:55:56.595877Z | Info | Live bytes: 941.79MB Heap size: 2177.89MB +2024-07-16T13:56:51.364767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:56:56.601076Z | Info | Live bytes: 940.24MB Heap size: 2177.89MB +2024-07-16T13:57:13.438398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:57:16.398230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:57:16.442483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:57:56.613673Z | Info | Live bytes: 943.13MB Heap size: 2179.99MB +2024-07-16T13:58:33.768412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T13:58:34.032610Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-16T13:58:56.633788Z | Info | Live bytes: 970.77MB Heap size: 2188.38MB +2024-07-16T13:59:56.693609Z | Info | Live bytes: 970.77MB Heap size: 2188.38MB +2024-07-16T14:00:56.753758Z | Info | Live bytes: 970.77MB Heap size: 2188.38MB +2024-07-16T14:01:56.813476Z | Info | Live bytes: 970.77MB Heap size: 2188.38MB +2024-07-16T14:02:56.849499Z | Info | Live bytes: 970.77MB Heap size: 2188.38MB +2024-07-16T14:03:56.874488Z | Info | Live bytes: 970.77MB Heap size: 2188.38MB +2024-07-16T14:04:56.888621Z | Info | Live bytes: 969.13MB Heap size: 2190.48MB +2024-07-16T14:05:01.008113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:05:17.617812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:05:20.404857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:05:56.915455Z | Info | Live bytes: 841.60MB Heap size: 2649.75MB +2024-07-16T14:06:45.744660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:06:56.918670Z | Info | Live bytes: 866.06MB Heap size: 2649.75MB +2024-07-16T14:07:56.979588Z | Info | Live bytes: 866.06MB Heap size: 2649.75MB +2024-07-16T14:08:57.039609Z | Info | Live bytes: 897.91MB Heap size: 2649.75MB +2024-07-16T14:09:57.099593Z | Info | Live bytes: 902.89MB Heap size: 2649.75MB +2024-07-16T14:10:53.306993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:10:57.122970Z | Info | Live bytes: 920.22MB Heap size: 2649.75MB +2024-07-16T14:11:57.183528Z | Info | Live bytes: 940.81MB Heap size: 2649.75MB +2024-07-16T14:12:09.441168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:12:57.243493Z | Info | Live bytes: 976.07MB Heap size: 2649.75MB +2024-07-16T14:13:25.068803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:13:56.175460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:13:56.970116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:13:57.245209Z | Info | Live bytes: 978.20MB Heap size: 2649.75MB +2024-07-16T14:13:58.693136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:13:59.279812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:13:59.921883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:00.542334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:18.209170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:19.289621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:20.356275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:40.158419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:52.423674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:53.787387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:54.788495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:55.950582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:56.553153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:14:57.246573Z | Info | Live bytes: 1025.05MB Heap size: 2649.75MB +2024-07-16T14:15:57.298544Z | Info | Live bytes: 1025.05MB Heap size: 2649.75MB +2024-07-16T14:16:57.358610Z | Info | Live bytes: 1025.05MB Heap size: 2649.75MB +2024-07-16T14:17:57.418557Z | Info | Live bytes: 1025.05MB Heap size: 2649.75MB +2024-07-16T14:18:57.474480Z | Info | Live bytes: 1025.05MB Heap size: 2649.75MB +2024-07-16T14:19:45.647828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-16T14:19:57.478503Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:20:57.539432Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:21:57.599487Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:22:57.659523Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:23:57.720309Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:24:57.780470Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:25:57.805667Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:26:57.865513Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:27:57.925511Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:28:57.968599Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:29:57.983618Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:30:58.044221Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:31:58.104806Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:32:58.135564Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:33:58.195783Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:34:58.257107Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:35:58.318230Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:36:58.329833Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:37:58.374119Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:38:58.409932Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:39:58.471702Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:40:58.533547Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:41:58.595319Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:42:58.656874Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:43:58.718847Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:44:58.769855Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:45:58.831486Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:46:58.892728Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:47:58.953916Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:48:59.015789Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:49:59.077068Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:50:59.137739Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:51:59.198895Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:52:59.260536Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:53:59.321549Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:54:59.382638Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:55:59.434558Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:56:59.494641Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:57:59.513847Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:58:59.575237Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T14:59:59.619471Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:00:59.680596Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:01:59.741376Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:02:59.801529Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:03:59.861586Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:04:59.922456Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:05:59.982635Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:07:00.042499Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:08:00.102487Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:09:00.162512Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:10:00.222709Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:11:00.236835Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:12:00.296540Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:13:00.347998Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:14:00.409531Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:15:00.471073Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:16:00.532536Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:17:00.586538Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:18:00.647882Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:19:00.673916Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:20:00.735463Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:21:00.796864Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:22:00.857592Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:23:00.917542Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:24:00.978619Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:25:01.040071Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:26:01.081866Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:27:01.143329Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:28:01.204748Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:29:01.266060Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:30:01.327410Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:31:01.388793Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:32:01.450279Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:33:01.457957Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:34:01.519455Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:35:01.580757Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:36:01.642103Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:37:01.703583Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:38:01.765139Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:39:01.793960Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:40:01.855512Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:41:01.916852Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:42:01.978289Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:43:02.039754Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:44:02.041859Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:45:02.103169Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:46:02.129950Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:47:02.191442Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:48:02.252870Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:49:02.314216Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:50:02.375332Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:51:02.436601Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:52:02.487823Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:53:02.544296Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:54:02.558589Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:55:02.573103Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:56:02.585987Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:57:02.643216Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:58:02.701490Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T15:59:02.762680Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:00:02.801912Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:01:02.863224Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:02:02.873782Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:03:02.925789Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:04:02.973730Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:05:03.033850Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:06:03.095212Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:07:03.156611Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:08:03.206861Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:09:03.268026Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:10:03.327516Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:11:03.388274Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:12:03.449269Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:13:03.489698Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:14:03.551024Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:15:03.611780Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:16:03.671598Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:17:03.673848Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:18:03.733601Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:19:03.769545Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:20:03.830567Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:21:03.891570Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:22:03.897664Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:23:03.958618Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:24:03.961711Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:25:03.993622Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:26:04.054166Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:27:04.070640Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:28:04.077578Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:29:04.137672Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:30:04.154336Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:31:04.215623Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:32:04.277033Z | Info | Live bytes: 1039.91MB Heap size: 2649.75MB +2024-07-16T16:32:30.921822Z | Error | Got EOF +2024-07-17 07:07:14.2480000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-17 07:07:14.2490000 [client] INFO Finding haskell-language-server +2024-07-17 07:07:14.2530000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:14.2530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:14.2610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-17 07:07:14.8660000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:14.8660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:14.8740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-17 07:07:15.1560000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:15.1560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:15.1650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-17 07:07:15.3830000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:15.3830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:15.3950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-17 07:07:15.6070000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:15.6080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:15.6130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-17 07:07:15.6300000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:15.6300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:15.6370000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-17 07:07:15.6550000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:15.6560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:15.6640000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-17 07:07:15.6890000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-17 07:07:15.8470000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:15.8470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:15.8530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-17 07:07:16.0690000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-17 07:07:16.0700000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-17 07:07:25.6780000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-17 07:07:25.9140000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-17 07:07:25.9140000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:25.9140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:25.9200000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-17 07:07:26.0050000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:26.0060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:26.0100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-17 07:07:26.0270000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:26.0270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:26.0320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-17 07:07:26.0460000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:26.0460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:26.0510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-17 07:07:26.0660000 [client] INFO Checking for ghcup installation +2024-07-17 07:07:26.0660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-17 07:07:26.0720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-17 07:07:26.2090000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-17 07:07:26.2100000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-17 07:07:26.2100000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-17 07:07:26.2100000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-17 07:07:26.2100000 [client] INFO server environment variables: +2024-07-17 07:07:26.2100000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-17 07:07:26.2100000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-17 07:07:26.2100000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-17 07:07:26.2120000 [client] INFO Starting language server +2024-07-17T07:07:38.304654Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-17T07:07:38.307100Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-17T07:07:38.307429Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T07:07:38.311010Z | Info | Logging heap statistics every 60.00s +2024-07-17T07:07:38.323789Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T07:07:38.324437Z | Info | Starting server +2024-07-17T07:07:38.342868Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-17T07:07:38.455232Z | Info | Started LSP server in 0.13s +2024-07-17T07:07:40.055064Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T07:07:40.056305Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T07:07:40.639893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:07:40.639997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:07:41.914164Z | Info | Load cabal cradle using single file +2024-07-17T07:07:43.280568Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT26710-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T07:07:47.703559Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-91ce7db861ce9f8a5fa5cdd35181cbff88842a76 +2024-07-17T07:07:47.715373Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-17T07:07:53.682019Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-17T07:07:53.683048Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T07:07:53.782957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:07:53.861577Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-17T07:07:54.304600Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-17T07:07:54.416754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:07:55.836571Z | Info | Load cabal cradle using single file +2024-07-17T07:07:56.999430Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT26710-11 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T07:08:38.351881Z | Info | Live bytes: 485.94MB Heap size: 1992.29MB +2024-07-17T07:09:17.801682Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-af8441dbb3602f7131921f13c15272adfaab98f9 +2024-07-17T07:09:17.802094Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-af8441dbb3602f7131921f13c15272adfaab98f9 +2024-07-17T07:09:17.814156Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.0.0.0-inplace + , cardano-api-9.0.0.0-inplace-internal ] +2024-07-17T07:09:24.948963Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-17T07:09:38.365825Z | Info | Live bytes: 1007.55MB Heap size: 2545.94MB +2024-07-17T07:10:38.418042Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:11:38.478994Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:12:38.539993Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:13:38.573002Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:14:38.626428Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:15:38.687593Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:16:38.748686Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:17:38.780395Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:18:38.840480Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:19:38.900527Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:20:38.957007Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:21:39.017883Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:22:39.045095Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:23:39.099801Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:24:39.161470Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:25:35.947916Z | Warning | LSP: no handler for: "$/setTrace" +2024-07-17T07:25:39.170653Z | Info | Live bytes: 1003.90MB Heap size: 2545.94MB +2024-07-17T07:25:57.581282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:25:59.312810Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:26:01.051802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:26:03.441645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:26:03.917079Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Sign.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-17T07:26:03.923588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:26:39.195717Z | Info | Live bytes: 1207.35MB Heap size: 2545.94MB +2024-07-17T07:27:02.737353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:27:39.230383Z | Info | Live bytes: 1295.42MB Heap size: 2545.94MB +2024-07-17T07:27:45.691187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:28:01.792010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:28:03.092536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:28:39.267669Z | Info | Live bytes: 1484.98MB Heap size: 2653.95MB +2024-07-17T07:29:39.328762Z | Info | Live bytes: 1484.98MB Heap size: 2653.95MB +2024-07-17T07:30:39.390440Z | Info | Live bytes: 1484.98MB Heap size: 2653.95MB +2024-07-17T07:31:39.452456Z | Info | Live bytes: 1484.98MB Heap size: 2653.95MB +2024-07-17T07:32:39.514378Z | Info | Live bytes: 1484.98MB Heap size: 2653.95MB +2024-07-17T07:33:39.516237Z | Info | Live bytes: 1040.15MB Heap size: 3405.77MB +2024-07-17T07:33:58.303279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:34:39.550503Z | Info | Live bytes: 1386.28MB Heap size: 3405.77MB +2024-07-17T07:35:39.567478Z | Info | Live bytes: 1398.18MB Heap size: 3405.77MB +2024-07-17T07:35:40.788675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:41.899779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:44.144182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:44.736142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:45.489416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:48.527472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:49.180138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:49.812919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:50.369035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:51.474994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:52.095561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:52.707389Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:53.330226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:55.652858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:57.810154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:58.736829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:35:59.345058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:00.019233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:04.478855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:05.108421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:06.369725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:07.439620Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:08.004805Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T07:36:08.475788Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T07:36:08.987089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:15.562392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:16.149341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:18.659057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:18.714402Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:18.891578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:19.063908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:19.222592Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:19.356121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:19.383244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:19.677871Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:20.149962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:21.058651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:21.156427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:21.237624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:21.274282Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:21.392670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:21.564001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:21.751199Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:21.870293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:21.913870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:22.081607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:22.556658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:22.972826Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:23.123605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:23.215520Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:23.303470Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:23.424417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:36:23.446355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:24.005363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:24.690662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:25.387331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:26.443059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:27.431500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:39.572655Z | Info | Live bytes: 1786.03MB Heap size: 3871.34MB +2024-07-17T07:36:39.706676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:54.273104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:36:58.308433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:37:03.242018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:37:03.456033Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:37:03.630573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:37:03.908951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:37:03.960388Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:37:04.710137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:37:05.673030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:37:09.740981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:37:18.710626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:37:39.589588Z | Info | Live bytes: 2019.09MB Heap size: 3871.34MB +2024-07-17T07:38:39.605118Z | Info | Live bytes: 2019.09MB Heap size: 3871.34MB +2024-07-17T07:39:39.666441Z | Info | Live bytes: 2019.09MB Heap size: 3871.34MB +2024-07-17T07:40:39.727935Z | Info | Live bytes: 2043.25MB Heap size: 3871.34MB +2024-07-17T07:41:39.751600Z | Info | Live bytes: 2043.25MB Heap size: 3871.34MB +2024-07-17T07:42:07.756865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:42:08.806821Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:42:09.459922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:42:10.445805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:42:39.777652Z | Info | Live bytes: 1031.66MB Heap size: 4126.15MB +2024-07-17T07:43:03.853142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:04.467767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:04.511615Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:43:04.749900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:43:05.092864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:43:05.188626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:05.208153Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:43:05.780080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:43:06.276036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:06.915423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:07.474307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:08.124279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:08.744925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:09.323580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:11.482500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:12.062679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:13.663085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:20.013774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:24.133165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:24.291084Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T07:43:25.175689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:39.791059Z | Info | Live bytes: 1169.50MB Heap size: 4126.15MB +2024-07-17T07:43:47.125771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:48.452423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:52.092332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:53.783277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:43:54.419565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:05.035231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:06.793172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:07.472668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:09.533079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:10.352340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:15.903307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:18.333848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:23.599539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:23.979192Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T07:44:24.865926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:32.556444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:33.055336Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T07:44:37.917197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:44:38.169498Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T07:44:39.792620Z | Info | Live bytes: 1373.01MB Heap size: 4126.15MB +2024-07-17T07:44:42.541401Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T07:44:42.561571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:45:39.850693Z | Info | Live bytes: 1388.09MB Heap size: 4126.15MB +2024-07-17T07:45:46.581751Z | Info | LSP: received shutdown +2024-07-17T07:45:46.585700Z | Error | Got EOF +2024-07-17T07:46:00.571526Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-17T07:46:00.572908Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-17T07:46:00.573361Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T07:46:00.576801Z | Info | Logging heap statistics every 60.00s +2024-07-17T07:46:00.586015Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T07:46:00.586655Z | Info | Starting server +2024-07-17T07:46:00.588766Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-17T07:46:00.675976Z | Info | Started LSP server in 0.09s +2024-07-17T07:46:02.287923Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T07:46:02.289141Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T07:46:02.933647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:46:02.933741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:46:04.027857Z | Info | Load cabal cradle using single file +2024-07-17T07:46:05.183068Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT82502-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T07:46:13.805284Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-c875534007e32f9c29d109be7ba71e4921e24ed2 +2024-07-17T07:46:13.813739Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-17T07:46:27.649568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:47:00.588897Z | Info | Live bytes: 708.63MB Heap size: 2043.67MB +2024-07-17T07:48:00.630885Z | Info | Live bytes: 708.63MB Heap size: 2043.67MB +2024-07-17T07:48:12.079482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:48:17.609893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:48:18.228791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:48:18.329024Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T07:49:00.651610Z | Info | Live bytes: 664.32MB Heap size: 2554.33MB +2024-07-17T07:49:09.668863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:10.319581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:11.216417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:11.399810Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:11.563219Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:11.868303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:12.010886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:12.517085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:13.143741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:13.764475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:14.998694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:16.227924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:16.850992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:20.158994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:21.484146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:21.721875Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:22.022112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:22.201241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:22.219090Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:22.367259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:22.826422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:25.690020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:34.014425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:34.143113Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:34.278784Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:34.390305Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:34.447169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:34.486572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:34.629029Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:35.044563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:49:35.081693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:35.882668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:49:40.891235Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T07:50:00.668385Z | Info | Live bytes: 1110.78MB Heap size: 2554.33MB +2024-07-17T07:51:00.728552Z | Info | Live bytes: 1110.78MB Heap size: 2554.33MB +2024-07-17T07:52:00.789697Z | Info | Live bytes: 1110.78MB Heap size: 2554.33MB +2024-07-17T07:52:16.593316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:52:17.667800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:53:00.829615Z | Info | Live bytes: 1168.66MB Heap size: 2554.33MB +2024-07-17T07:53:30.659504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:00.848752Z | Info | Live bytes: 1225.33MB Heap size: 2554.33MB +2024-07-17T07:54:31.679883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:34.553750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:38.376378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:40.166563Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-17T07:54:40.167544Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T07:54:40.246521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:42.210989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:43.278394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:44.820753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:45.465216Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T07:54:45.847031Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T07:54:46.385222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:46.971564Z | Info | Load cabal cradle using single file +2024-07-17T07:54:48.408305Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT82502-48 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T07:54:50.055799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:54:50.845448Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" +2024-07-17T07:54:52.428284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:55:00.854278Z | Info | Live bytes: 892.88MB Heap size: 3014.66MB +2024-07-17T07:55:24.638630Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:24.733142Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:24.927099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:24.984860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:55:25.004118Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:25.463202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:25.536864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:25.606605Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:25.696563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T07:55:25.872117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:55:26.657932Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T07:56:00.871495Z | Info | Live bytes: 1017.02MB Heap size: 3014.66MB +2024-07-17T07:57:00.932486Z | Info | Live bytes: 1017.02MB Heap size: 3014.66MB +2024-07-17T07:58:00.993650Z | Info | Live bytes: 1017.02MB Heap size: 3014.66MB +2024-07-17T07:59:00.999508Z | Info | Live bytes: 1030.35MB Heap size: 3014.66MB +2024-07-17T07:59:11.970502Z | Info | Cradle path: cardano-api/test/cardano-api-test/Test/Cardano/Api/Typed/Ord.hs +2024-07-17T07:59:11.971117Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T07:59:12.013986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T07:59:18.290740Z | Info | Load cabal cradle using single file +2024-07-17T07:59:19.990665Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:test:cardano-api-test + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT82502-51 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T07:59:54.670801Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/main-1ca2e38a7380c853ff0df647d3088be421fe5e01-1ca2e38a7380c853ff0df647d3088be421fe5e01 +2024-07-17T07:59:54.671191Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-1ca2e38a7380c853ff0df647d3088be421fe5e01 +2024-07-17T07:59:54.678552Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.0.0.0-inplace-internal + , main-1ca2e38a7380c853ff0df647d3088be421fe5e01 ] +2024-07-17T07:59:55.260117Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-17T07:59:55.261207Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T07:59:56.866716Z | Info | Load cabal cradle using single file +2024-07-17T07:59:57.882955Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT82502-52 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T08:00:01.004459Z | Info | Live bytes: 1100.68MB Heap size: 3014.66MB +2024-07-17T08:00:01.573489Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-9e21f019e6dcd9c3293d5ee7ef25ace2416b37d9 +2024-07-17T08:00:01.573755Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/main-1ca2e38a7380c853ff0df647d3088be421fe5e01-9e21f019e6dcd9c3293d5ee7ef25ace2416b37d9 +2024-07-17T08:00:01.573947Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-9e21f019e6dcd9c3293d5ee7ef25ace2416b37d9 +2024-07-17T08:00:01.580886Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.0.0.0-inplace + , cardano-api-9.0.0.0-inplace-internal + , main-1ca2e38a7380c853ff0df647d3088be421fe5e01 ] +2024-07-17T08:01:01.042402Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:02:01.103004Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:03:01.164234Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:04:01.225840Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:05:01.287722Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:06:01.349342Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:07:01.410662Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:08:01.472008Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:09:01.533423Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:10:01.594849Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:11:01.656240Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:12:01.717748Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:13:01.779338Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:14:01.840770Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:15:01.902245Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:16:01.963656Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:17:01.998474Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:18:02.059442Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:19:02.107722Z | Info | Live bytes: 1523.85MB Heap size: 3520.07MB +2024-07-17T08:19:08.219379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:19:16.810176Z | Info | LSP: received shutdown +2024-07-17T08:19:16.811668Z | Error | Got EOF +2024-07-17T08:19:22.199324Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-17T08:19:22.200322Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-17T08:19:22.200521Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:19:22.203435Z | Info | Logging heap statistics every 60.00s +2024-07-17T08:19:22.212059Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:19:22.212646Z | Info | Starting server +2024-07-17T08:19:22.214163Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-17T08:19:22.253577Z | Info | Started LSP server in 0.04s +2024-07-17T08:19:23.670743Z | Info | LSP: received shutdown +2024-07-17T08:19:23.671914Z | Info | Reactor thread stopped +2024-07-17T08:19:23.674859Z | Error | Got EOF +2024-07-17T08:19:29.009380Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-17T08:19:29.010397Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-17T08:19:29.010831Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:19:29.013978Z | Info | Logging heap statistics every 60.00s +2024-07-17T08:19:29.021809Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:19:29.022202Z | Info | Starting server +2024-07-17T08:19:29.023494Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-17T08:19:29.100056Z | Info | Started LSP server in 0.08s +2024-07-17T08:19:30.409841Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:19:30.410901Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T08:19:30.956044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:19:30.956114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:19:31.904720Z | Info | Load cabal cradle using single file +2024-07-17T08:19:32.903331Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT133333-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T08:19:36.340398Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-c875534007e32f9c29d109be7ba71e4921e24ed2 +2024-07-17T08:19:36.346237Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-17T08:19:40.238118Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-17T08:20:15.779152Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:15.779726Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:16.324451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:16.324513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:22.288686Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.288936Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.452676Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.453059Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.620058Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.620311Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.770103Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.770445Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:22.834676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:22.834767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:26.464278Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:26.464649Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:26.793646Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:26.793873Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:27.010086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:27.010179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:27.143230Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:27.143480Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:27.478492Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:27.478657Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:27.688694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:27.688808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:27.974165Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:27.974735Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:28.153381Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:28.153877Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:28.475348Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:28.475567Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:28.518224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:28.518300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:29.015631Z | Info | Live bytes: 616.66MB Heap size: 1810.89MB +2024-07-17T08:20:29.035881Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:29.036218Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:29.437489Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:29.437923Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:29.582205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:29.582291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:30.655839Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:30.656297Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:31.050263Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:31.050743Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:31.201037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:31.201300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:31.217203Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:31.217589Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:31.757445Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:31.757670Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:31.761250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:31.761713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:32.206527Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:32.207119Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:32.568508Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:32.568895Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:32.752244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:32.752501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:43.398548Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:43.398796Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:43.668984Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:43.669233Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:43.944141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:43.944300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:49.296297Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:49.296612Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:49.842512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:49.842557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:51.162643Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:51.163049Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:51.707284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:51.707339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:54.116301Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:54.116802Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:54.662580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:54.662641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:55.634816Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:20:55.905490Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:55.905739Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:56.459421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:56.459509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:57.618625Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:57.618853Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:20:58.163036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:58.163220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:20:59.059737Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:21:00.274322Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:00.274697Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:00.820702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:00.821587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:01.513741Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:21:12.680456Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:12.680626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:21.631355Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:21.631749Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:21.892640Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:21.892968Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:21.956794Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:21.957221Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.158402Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.158890Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.176209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:22.176514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:22.228965Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.229414Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.248129Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.248384Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.335330Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.335718Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.488759Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.489413Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.759826Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.760573Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:22.783470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:22.783829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:23.117947Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:21:23.378368Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:23.378703Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:23.412600Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:21:23.923673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:23.923759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:29.021070Z | Info | Live bytes: 592.00MB Heap size: 2318.40MB +2024-07-17T08:21:30.999319Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-17T08:21:31.503353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:31.503489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:49.125490Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:49.125788Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:49.671089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:49.671089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:50.028088Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.028433Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.249860Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.250091Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.420454Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.420908Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.568954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:50.568987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:50.578069Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.578395Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.756963Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:50.757422Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:51.123838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:51.123942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:51.817177Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:51.817685Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.164458Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.164772Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.327602Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.327904Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.361400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:52.361400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:52.390766Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.391020Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.829505Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.829866Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:52.936712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:52.936759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:53.004440Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.004857Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.165320Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.165695Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.223782Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.224024Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.301267Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.301659Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.422191Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.422689Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.550181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:53.550501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:53.976414Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:53.976874Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:54.086350Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:54.086771Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:54.284854Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:54.285205Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:54.469280Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:54.469694Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:54.521858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:54.522030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:55.195237Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.195751Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.320307Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.320668Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.446847Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.447346Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.606245Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.606695Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.740539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:55.740539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:55.955056Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:55.955267Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.117841Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.118105Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.233581Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.233931Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.336754Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.336980Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.455061Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.455429Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.501092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:56.501315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:56.633708Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.634102Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.768225Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.768733Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.931032Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:56.931444Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.092898Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.093344Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.179380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:57.180391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:57.253107Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.253475Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.389632Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.390058Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.452092Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.452565Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.528827Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.529329Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.609730Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.610129Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.754724Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.755055Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.798715Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:57.798921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:57.864625Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.865066Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.944923Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:57.945331Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:58.035775Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:58.036135Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:58.409486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:58.409527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:58.472750Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:58.472935Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:58.835176Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:58.835411Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.019734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:59.019848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:59.168412Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.168626Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.302573Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.303073Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.536144Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.536535Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.661706Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.662016Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.714072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:59.714740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:21:59.847978Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:21:59.848352Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:00.052800Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:00.053158Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:00.278904Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:00.279085Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:00.393276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:00.393276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:00.989692Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:00.990047Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:01.305217Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:01.305820Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:01.406987Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:01.407355Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:01.534234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:01.534442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:02.209398Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.209737Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.390550Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.390926Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.440559Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.440789Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.573053Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.573462Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.618728Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.619177Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.688911Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.689401Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.754140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:02.754388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:02.757724Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.757953Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.926393Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:02.926839Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.220319Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.220648Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.302681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:03.302708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:03.407627Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.408058Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.632263Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.632570Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.744749Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.745187Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.954069Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.954321Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:03.969898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:03.969969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:04.078381Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:04.078607Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:04.623475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:04.624073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:04.958035Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:04.958483Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.091603Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.091917Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.253298Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.253626Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.337994Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.338234Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.503465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:05.503484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:05.546506Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:05.546784Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:06.091550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:06.091658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:06.756407Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:06.756637Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:06.984187Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:06.984499Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:07.063417Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:07.063820Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:07.174179Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:07.174626Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:07.302725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:07.302779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:07.948948Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:07.949415Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:08.047595Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:08.048047Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:08.494240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:08.494325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:08.536271Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:08.536603Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.082093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:09.082413Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:09.177600Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.178063Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.248829Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.249290Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.319632Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.319851Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.723082Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:09.723107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:09.778443Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:09.778613Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:10.322997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:10.323163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:10.447474Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:10.447861Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:10.795159Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:10.795552Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:10.992067Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:10.992474Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:11.004064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:11.004391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:11.943283Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:11.943598Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:12.304715Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:22:12.488151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:12.488234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:22.514980Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:22.515184Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:22.844163Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:22.844406Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:23.059993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:23.060035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:25.964394Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:25.964622Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:26.128399Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:26.128830Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:26.304211Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:26.304639Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:26.509283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:26.509325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:26.597925Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:26.598281Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:27.147623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:27.147856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:29.024601Z | Info | Live bytes: 707.52MB Heap size: 2605.71MB +2024-07-17T08:22:30.127553Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.127837Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.241634Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.242108Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.333738Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.333942Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.459597Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.460107Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.531013Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.531514Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.673361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:30.673475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:30.682240Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.682753Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.845449Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:30.845957Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:31.155893Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:31.156161Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:31.226793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:31.226804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:31.347745Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:31.348167Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:31.409646Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:31.410129Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:31.893373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:31.893419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:36.700272Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:36.700565Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:37.244693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:37.244790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:37.755452Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:37.755856Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.301063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:38.301166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:38.396719Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.397050Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.531090Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.531589Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.616376Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.616601Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.715144Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.715516Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.854315Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.854646Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:38.942934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:38.943022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:40.932867Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:40.933317Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.139338Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.139539Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.219646Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.219941Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.288393Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.288761Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.335559Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.336078Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.428354Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.428697Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.477286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:41.477397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:41.516757Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.517170Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.601826Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:41.602323Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.063056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:42.063600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:42.354746Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.355329Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.506356Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.506830Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.634498Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.634887Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.733208Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.733674Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.854026Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.854304Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.900577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:42.900639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:42.972590Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:42.973118Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:43.295652Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:43.295952Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:43.486430Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:43.486852Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:43.516919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:43.516919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:43.791597Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:43.791939Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:44.336747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:44.336874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:44.435366Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:44.435728Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:44.531675Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:44.532151Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:44.981446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:44.981475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:45.142115Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.142634Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.289681Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.290187Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.461638Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.461985Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.543911Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.544356Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.619310Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.619706Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.687867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:45.687881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:45.784227Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:45.784633Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:22:46.331969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:46.332234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:52.496962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:52.497033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:53.642454Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:22:53.642997Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:22:54.187321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:54.187375Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:54.593435Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:22:54.593743Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:22:55.138694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:22:55.138744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:00.753342Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:00.753688Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:01.025716Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:01.026061Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:01.313670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:01.313676Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:02.687594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:02.687795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:06.568511Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:06.568786Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:06.793440Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:06.793658Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:07.117622Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:23:07.127645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:07.127644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:12.221103Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:12.221463Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:12.765510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:12.765512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:13.405118Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:13.405585Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:13.609726Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:13.609969Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:13.823164Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:13.823529Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:13.949801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:13.949872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:14.095164Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:14.095627Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:14.639367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:14.639607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:17.291924Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:17.292267Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:17.514763Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:17.515143Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:17.678383Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:17.678821Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:17.836836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:17.836909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:17.879516Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:17.879770Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:18.253888Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:23:18.424404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:18.424581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:18.568292Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:18.568689Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:18.595874Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:23:19.113306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:19.113380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:23.794530Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:23.795025Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:24.143503Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:24.143726Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:24.339551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:24.339650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:24.502583Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:23:29.028888Z | Info | Live bytes: 598.02MB Heap size: 2743.07MB +2024-07-17T08:23:44.180250Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:44.180592Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:44.725062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:44.725245Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:45.913146Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:45.913368Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:46.461201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:46.461371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:46.478024Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:46.478289Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:46.604543Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:46.604896Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:46.763383Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:46.763870Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:47.007400Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:47.007792Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:47.034789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:47.034788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:49.707222Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:49.707530Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:50.252655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:50.253073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:50.866379Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:50.866768Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:51.410870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:51.410999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:51.859959Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:51.860444Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:52.404990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:52.405205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:53.987630Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:53.988073Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:54.535653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:54.535722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:56.047159Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:56.047525Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:56.389736Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:56.390078Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:56.594648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:56.594712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:57.929030Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:57.929360Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:23:58.463136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:58.463204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:23:58.932546Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:24:12.338058Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:12.338517Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:12.882914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:12.882926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:14.028561Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.028827Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.204560Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.204968Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.463106Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.463466Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.570431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:14.570441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:14.743650Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.744000Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.888122Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:14.888465Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:15.289726Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:15.290036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:15.292190Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:15.292354Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:15.837540Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:15.837663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:15.865220Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:15.865553Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:16.354969Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:16.355399Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:16.409360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:16.409384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:16.741051Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:16.741580Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:17.121309Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:17.121560Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:24:17.287458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:17.287523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:29.041864Z | Info | Live bytes: 1032.09MB Heap size: 2743.07MB +2024-07-17T08:24:30.105288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:30.105421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:48.396419Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:48.396648Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:48.519212Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:48.519637Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:48.942950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:48.943050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:49.726156Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:49.726679Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:49.971390Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:49.971668Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:50.072369Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:50.072734Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:50.271159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:50.271335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:50.415134Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:50.415431Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:50.694744Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:50.695080Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:50.973740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:50.973744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:51.369266Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.369517Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.512316Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.512822Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.633414Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.633945Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.741310Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.741965Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.807120Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.807579Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.872511Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.872808Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:51.914719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:51.914749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:52.155942Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:52.156277Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:52.702309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:52.702499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:52.709332Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:52.709832Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.255406Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:53.255667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:53.376680Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.376954Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.690050Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.690370Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.836584Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.837023Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.922533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:53.922533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:53.993967Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:53.994367Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.540647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:54.540661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:54.675941Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.676366Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.787713Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.788219Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.850202Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.850810Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.995909Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:54.996441Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:55.089626Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:55.090081Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:55.220703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:55.220820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:56.213664Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:56.213990Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:56.321508Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:56.322012Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:56.441741Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:56.442021Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:24:56.757870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:24:56.757870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:25:29.075911Z | Info | Live bytes: 538.01MB Heap size: 2743.07MB +2024-07-17T08:26:29.137214Z | Info | Live bytes: 538.01MB Heap size: 2743.07MB +2024-07-17T08:27:29.179832Z | Info | Live bytes: 538.01MB Heap size: 2743.07MB +2024-07-17T08:28:29.241336Z | Info | Live bytes: 538.01MB Heap size: 2743.07MB +2024-07-17T08:28:48.919118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:28:48.919220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:28.380605Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:28.380853Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:28.927767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:28.928188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:29.243546Z | Info | Live bytes: 605.36MB Heap size: 2743.07MB +2024-07-17T08:29:35.194379Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:35.194592Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:35.411215Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:35.411557Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:35.748942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:35.749001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:38.354408Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:38.354646Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:38.782107Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:38.782377Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:38.899778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:38.899865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:39.603523Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:39.603787Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:39.734391Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:39.734791Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.051265Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.051514Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.152181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:40.152181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:40.329906Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.330213Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.798341Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.798641Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.874562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:40.874563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:40.941174Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:40.941640Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.037898Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.038188Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.180564Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.181007Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.491217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:41.491217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:41.516755Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.517177Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.640549Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.640830Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.778663Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.779023Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.863171Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.863543Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.955355Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:41.955818Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:42.038476Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:42.038992Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:42.061174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:42.061167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:42.381000Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:42.381302Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:42.589689Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:42.589956Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:42.935398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:42.941947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:43.535513Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:43.535873Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:43.643555Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:43.643943Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:43.767464Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:43.767808Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:43.986844Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:43.987139Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.079777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:44.079870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:44.200399Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.200632Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.307792Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.308076Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.424934Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.425383Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.553096Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.553453Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:44.747865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:44.747928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:45.141451Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:45.141874Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:45.686109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:45.686155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:46.493736Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:46.494119Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:46.933939Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:46.934295Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.041328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:47.041364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:47.099300Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.099718Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.261199Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.261484Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.460590Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.461001Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.539601Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.539924Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.626749Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.627118Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.649562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:47.649584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:47.949919Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:47.950236Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:48.415018Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:48.415248Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:48.495854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:48.496758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:49.768729Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:49.769094Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:50.314437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:50.314555Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:50.881161Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:50.881376Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.145416Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.145912Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.428626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:51.428660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:51.586957Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.587374Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.806680Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.806939Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.898718Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:51.899104Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.031012Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.031508Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.096048Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.096551Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.131697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:52.131697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:52.139639Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.139923Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.429939Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.430223Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.674430Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.674640Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.697670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:52.697671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:52.778238Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:52.778493Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:53.324574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:53.324614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:53.870470Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:53.870917Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.011076Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.011459Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.114888Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.115300Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.231443Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.231890Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.294373Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.294945Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.370690Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.371097Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.415964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:54.416247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:54.541218Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.541682Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.650575Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.650779Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.789790Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:54.790034Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.092123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:55.092185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:55.254640Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.255097Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.336067Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.336354Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.553541Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.553827Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.770356Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.770633Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.800021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:55.800057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:55.879863Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:55.880055Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:56.426618Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:56.427030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:57.120824Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:57.121204Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:57.667866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:57.667980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:58.289705Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:58.290022Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:58.468655Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:58.468933Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:29:58.846613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:29:58.846703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:04.125662Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:04.126174Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:04.470854Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:04.471190Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:04.671900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:04.673187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:05.034167Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:05.034502Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:05.579470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:05.579502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:09.859519Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:09.859889Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:09.996865Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:09.997245Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.109344Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.109785Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.241500Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.242096Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.404562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:10.404911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:10.422474Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.422902Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.713619Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.714019Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:10.970884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:10.970979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:11.079146Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.079528Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.232303Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.232685Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.295069Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.295581Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.364722Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.365249Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.439092Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.439479Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.519981Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.520455Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.612955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:11.613422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:11.621614Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.621991Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.685172Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:11.685699Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:12.166500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:12.166558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:25.025944Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.026202Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.154853Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.155184Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.289283Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.289718Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.371112Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.371666Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.486247Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.486669Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.571769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:25.571892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:25.629321Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:25.629736Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.175728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:26.175755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:26.203114Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.203572Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.367447Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.367889Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.456487Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.457026Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.519588Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.519924Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.598957Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.599345Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.703781Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.704078Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.748639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:26.748942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:26.780748Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.781243Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.843139Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:26.843654Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:27.326498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:27.326697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:28.614425Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-17T08:30:29.246433Z | Info | Live bytes: 986.42MB Heap size: 2743.07MB +2024-07-17T08:30:37.791487Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:37.791803Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:38.154561Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:38.154852Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:38.336589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:38.336591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:38.347149Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:38.347653Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:38.891803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:38.891908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:40.987491Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:40.987782Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:41.128471Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:41.128989Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:41.517104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:41.517104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:41.756355Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:41.756791Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:41.825358Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:41.825658Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:42.301588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:42.301588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:44.646661Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:44.647018Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:45.191655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:45.191699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:46.274060Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:46.274406Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:30:46.877728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:46.877786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:46.890006Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-17T08:30:48.235160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:48.235705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:52.239947Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:52.240396Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:52.784864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:52.785140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:54.343693Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:54.344127Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:54.537515Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:54.538167Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:54.718093Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:54.718589Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:54.890109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:54.890481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:55.209017Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:55.209590Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:55.755217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:55.755281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:56.525782Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:56.526017Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:56.672348Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:56.672730Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:57.072723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:57.072952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:57.380219Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:57.380479Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:57.924398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:57.924546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:58.881845Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:58.882401Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:59.032745Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:59.033291Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:30:59.428001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:30:59.428009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:00.546575Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:00.547075Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:00.669091Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:00.669542Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:00.780196Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:00.780517Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:00.913392Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:00.913898Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.036806Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.037227Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.092289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:01.092306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:01.147754Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.148300Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.257136Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.257629Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.592205Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.592583Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.693286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:01.693324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:01.973846Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:01.974072Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.095031Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.095496Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.194752Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.195183Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.293921Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.294299Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.334196Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.334583Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.406922Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.407240Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:02.519476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:02.519765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:05.944435Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:05.944655Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:06.242537Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:06.242761Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:06.490136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:06.491000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:08.083648Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:08.084033Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:08.338330Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:08.338898Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:08.627943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:08.628018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:08.677608Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:31:29.250374Z | Info | Live bytes: 1074.19MB Heap size: 2797.60MB +2024-07-17T08:31:48.125928Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:48.126467Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:48.670804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:48.670815Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:49.461824Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:49.462195Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:49.630367Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:49.630679Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:50.007023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:50.007139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:51.805215Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:51.805612Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:52.351395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:52.352369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:52.976655Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:52.977117Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:53.523396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:53.523636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:53.668374Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:31:53.925065Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:53.925505Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:31:53.949408Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:31:54.470404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:31:54.470596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:03.856274Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:03.856821Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:04.402751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:04.403084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:04.927985Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:32:05.194535Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:05.195018Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:05.214865Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:32:05.739133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:05.739138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:07.032616Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:07.033267Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:07.578360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:07.578506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:07.937102Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:32:18.497244Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.497484Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.665536Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.665825Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.785352Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.785595Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.838843Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.839095Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.923648Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.923955Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.988918Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:18.989197Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:19.041988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:19.042071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:19.056199Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:19.056555Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:19.125951Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:19.126160Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:19.601694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:19.601759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:22.758915Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:22.759221Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:22.876609Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:22.876784Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:22.971777Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:22.972120Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:23.079636Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:23.080069Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:23.305721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:23.305894Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:23.951323Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:23.951550Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:24.079215Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:24.079663Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:24.496589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:24.496639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:24.905912Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:24.906415Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.073523Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.073969Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.156440Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.156804Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.229948Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.230314Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.386654Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.387087Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.451981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:25.452164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:25.480280Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.480624Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.578447Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.578801Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.666240Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:25.666586Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:26.024996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:26.025057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:26.164507Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:26.164771Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:26.711605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:26.711711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:29.252215Z | Info | Live bytes: 976.66MB Heap size: 2797.60MB +2024-07-17T08:32:29.704721Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:29.705075Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:30.250416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:30.250490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:30.344477Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:30.344916Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:30.689319Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:30.689570Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:30.890470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:30.890975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:31.066884Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.067154Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.314822Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.315136Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.444052Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.444346Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.550718Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.551080Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.613419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:31.613902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:31.645533Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:31.645952Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:32.192231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:32.192617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:33.405587Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.406005Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.595482Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.595818Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.736655Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.737029Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.839851Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.840358Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.915044Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.915620Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.949954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:33.950132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:33.953245Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:33.953426Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.186823Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.187112Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.343962Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.344316Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.439131Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.439650Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.501178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:34.501806Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:34.720804Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.721086Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.909986Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:34.910280Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.104920Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.105293Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.202163Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.202680Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.267731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:35.267837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:35.311570Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.311998Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.379728Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.379949Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.524302Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.524644Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:32:35.856981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:32:35.857110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:05.699895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:05.700116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:09.896024Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:09.896474Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.075320Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.075734Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.259291Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.259532Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.366088Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.366517Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.440903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:10.441061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:10.462425Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.462870Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.551379Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.551699Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.620679Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.620943Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.783277Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:10.783613Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:11.008654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:11.009063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:11.332377Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:11.332788Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:11.877649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:11.877691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:12.576531Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:12.576992Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:12.678877Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:12.679408Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:13.121733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:13.122118Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:14.101200Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:14.101621Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:14.646878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:14.647011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:15.183356Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:15.183619Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:15.728673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:15.728698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:16.152940Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.153324Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.525214Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.525479Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.645272Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.645725Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.697666Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:16.698327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:16.829065Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.829492Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.907372Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.907858Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.974402Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:16.974781Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.063436Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.063936Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.151453Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.151921Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.261669Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.262111Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.317058Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.317448Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.374460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:17.374475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:17.399645Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.399982Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.534412Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.534875Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:17.944843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:17.944942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:18.624872Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:33:18.902192Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:18.902666Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:18.924243Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:33:19.448796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:19.448840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:20.179130Z | Info | LSP: received shutdown +2024-07-17T08:33:20.181249Z | Error | Got EOF +2024-07-17T08:33:25.565966Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-17T08:33:25.566955Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-17T08:33:25.567231Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:33:25.571025Z | Info | Logging heap statistics every 60.00s +2024-07-17T08:33:25.579433Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:33:25.579909Z | Info | Starting server +2024-07-17T08:33:25.581743Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-17T08:33:25.623996Z | Info | Started LSP server in 0.04s +2024-07-17T08:33:27.057818Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-17T08:33:27.058491Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T08:33:27.605385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:27.605479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:33:28.760497Z | Info | Load cabal cradle using single file +2024-07-17T08:33:29.718160Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT153694-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T08:33:50.776466Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-07-17T08:33:50.776964Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T08:33:52.207975Z | Info | Load cabal cradle using single file +2024-07-17T08:33:53.123833Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT153694-1 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T08:33:56.431614Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-c875534007e32f9c29d109be7ba71e4921e24ed2 +2024-07-17T08:33:56.437141Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-17T08:33:56.736720Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-17T08:33:56.737547Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T08:33:58.577491Z | Info | Load cabal cradle using single file +2024-07-17T08:33:59.599460Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT153694-2 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T08:34:08.670396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:19.635193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:25.573466Z | Info | Live bytes: 447.88MB Heap size: 1740.64MB +2024-07-17T08:34:38.286883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:40.919163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:40.940537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:47.833094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:50.120060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:50.791130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:51.574996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:54.841330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:58.031683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:58.878756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:34:59.254209Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-07-17T08:35:25.579286Z | Info | Live bytes: 846.28MB Heap size: 2185.23MB +2024-07-17T08:36:12.172056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:21.757262Z | Info | LSP: received shutdown +2024-07-17T08:36:21.758508Z | Error | Got EOF +2024-07-17T08:36:30.916620Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-17T08:36:30.917441Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-17T08:36:30.917690Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:36:30.921583Z | Info | Logging heap statistics every 60.00s +2024-07-17T08:36:30.931975Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-17T08:36:30.932458Z | Info | Starting server +2024-07-17T08:36:30.934323Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-17T08:36:31.000230Z | Info | Started LSP server in 0.07s +2024-07-17T08:36:32.354708Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-17T08:36:32.355387Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T08:36:32.893636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:32.893649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:33.825874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:33.976628Z | Info | Load cabal cradle using single file +2024-07-17T08:36:34.956131Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT159224-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T08:36:35.969559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:37.041780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:38.416925Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-c875534007e32f9c29d109be7ba71e4921e24ed2 +2024-07-17T08:36:38.422606Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-17T08:36:38.750921Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-17T08:36:38.751649Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-17T08:36:40.172167Z | Info | Load cabal cradle using single file +2024-07-17T08:36:41.136712Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT159224-1 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-17T08:36:41.337903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:41.941360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:44.599108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:48.770209Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:49.367883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:50.393955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:50.944544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:51.413850Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-9e21f019e6dcd9c3293d5ee7ef25ace2416b37d9 +2024-07-17T08:36:51.414053Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-9e21f019e6dcd9c3293d5ee7ef25ace2416b37d9 +2024-07-17T08:36:51.418904Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.0.0.0-inplace + , cardano-api-9.0.0.0-inplace-internal ] +2024-07-17T08:36:52.057743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:52.772490Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:36:54.971167Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:36:55.475266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:36:55.762799Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:36:55.762798Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:37:01.642006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:04.234427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:06.455268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:06.952294Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:07.085499Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:07.108580Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:07.261950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:07.345968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:07.438052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:07.567727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:07.765183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:08.316974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:08.892159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:09.553384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:10.108767Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:10.793405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:11.700649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:12.017446Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:12.258652Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:12.500828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:13.116872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:13.843028Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.070661Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.073169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:14.228304Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.324286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.391329Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.470993Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.530816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.649662Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:14.729746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:15.293688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:15.841530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:16.479165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:17.072111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:17.707298Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:18.731756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:19.568958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:20.248303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:21.377015Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:21.535979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:21.570824Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:21.679362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:22.176299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:23.583404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:24.556654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:27.647842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:28.309706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:28.572523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:28.858770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:29.401932Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:29.514470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:29.673407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:29.792939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:37:30.164854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:30.651018Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:37:30.922872Z | Info | Live bytes: 1197.60MB Heap size: 2537.55MB +2024-07-17T08:37:47.730225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:48.413439Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:37:48.679129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:51.168636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:37:51.698583Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:37:57.453414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:38:30.937556Z | Info | Live bytes: 900.12MB Heap size: 2877.29MB +2024-07-17T08:39:30.971710Z | Info | Live bytes: 900.12MB Heap size: 2877.29MB +2024-07-17T08:40:31.032487Z | Info | Live bytes: 916.47MB Heap size: 2877.29MB +2024-07-17T08:40:38.330935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:40.632562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:43.008848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:43.933594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:44.605414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:46.318280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:47.748865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:48.737940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:48.792054Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:49.114155Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:49.285571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:49.409293Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:49.543114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:49.908547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:50.346861Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:50.570636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:50.799256Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:50.844990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:50.919716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:51.001569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:51.090549Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:51.279169Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:51.408235Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:54.945204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:55.084608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:55.192998Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:55.473854Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:55.690272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:56.101014Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:56.593724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:40:56.861751Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:57.146228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:40:57.353503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:31.034375Z | Info | Live bytes: 882.13MB Heap size: 3146.78MB +2024-07-17T08:41:51.672585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:52.448289Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:52.448483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:52.512845Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:53.007617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:53.099715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:53.192591Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:53.277393Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:53.454496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:53.585204Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:53.763026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:54.253653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:55.634863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:55.797023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:55.985776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:56.126601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:56.854186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:57.124332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:41:57.349229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:58.302186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:59.005377Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:41:59.611817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:00.217917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:00.821799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:01.463749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:02.215468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:42:02.381857Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:42:02.446409Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:42:02.700262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:03.500896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:04.026332Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:42:04.454901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:05.071359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:07.734797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:08.556446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:09.772933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:12.434289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:13.057376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:42:31.047519Z | Info | Live bytes: 1228.79MB Heap size: 3146.78MB +2024-07-17T08:43:31.066495Z | Info | Live bytes: 1238.55MB Heap size: 3146.78MB +2024-07-17T08:44:31.127330Z | Info | Live bytes: 1238.55MB Heap size: 3146.78MB +2024-07-17T08:45:31.188680Z | Info | Live bytes: 1238.55MB Heap size: 3146.78MB +2024-07-17T08:46:31.250054Z | Info | Live bytes: 1238.55MB Heap size: 3146.78MB +2024-07-17T08:47:31.311294Z | Info | Live bytes: 1238.55MB Heap size: 3146.78MB +2024-07-17T08:48:31.372466Z | Info | Live bytes: 1238.55MB Heap size: 3146.78MB +2024-07-17T08:49:23.864690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:24.658795Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:25.205886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:25.555259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:25.779076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:25.812901Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:26.013652Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:26.099478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:26.340850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:26.478270Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:26.501652Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:26.551934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:27.048045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:31.376556Z | Info | Live bytes: 773.65MB Heap size: 3146.78MB +2024-07-17T08:49:43.733958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:44.992205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:46.381194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:55.857007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:56.222464Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:56.412008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:56.719036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:57.340340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:58.025506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:58.584481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:59.310997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:49:59.334224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:59.429262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:59.500328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:59.603790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:59.775955Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:49:59.927602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:00.482919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:01.421690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:02.005416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:02.909567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:02.971454Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:03.102234Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:03.195770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:03.473172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:03.851178Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:50:04.142394Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T08:50:04.653621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:07.822185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:08.115453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:08.665719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:10.363922Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:10.618569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:13.140346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:25.463746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:26.114419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:31.377494Z | Info | Live bytes: 1418.98MB Heap size: 3146.78MB +2024-07-17T08:50:31.799069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:32.239463Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:32.628793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:32.780167Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:33.119367Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:33.165862Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:33.204271Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:33.289421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:33.938938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:35.774466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:41.879877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:56.347776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:56.707713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:57.726763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:58.475535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:59.234424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:59.289783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:50:59.316583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:59.351292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:50:59.860577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:01.425310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:03.302300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:06.278675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:09.464414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:11.261643Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:51:11.436366Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:51:11.472543Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:11.566382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:51:11.764171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:51:12.065074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:12.688515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T08:51:13.178994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:14.036421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:15.620891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:16.840787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:17.756007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:21.061918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:30.427615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:31.379832Z | Info | Live bytes: 1169.55MB Heap size: 3219.13MB +2024-07-17T08:51:31.685664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:32.268878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:32.869099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:48.600477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:49.277387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:49.846677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:50.507391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:51:51.209990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:52:01.369613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T08:52:31.387792Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T08:53:31.449020Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T08:54:31.509927Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T08:55:31.571409Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T08:56:31.632735Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T08:57:31.693692Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T08:58:31.728601Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T08:59:31.788369Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:00:31.843498Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:01:31.903415Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:02:31.963979Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:03:31.991602Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:04:32.051440Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:05:32.111530Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:06:32.171446Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:07:32.206514Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:08:32.258465Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:09:32.319452Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:10:32.344630Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:11:32.372410Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:12:32.377409Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:13:32.409348Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:14:32.470558Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:15:32.503996Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:16:32.513019Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:17:32.574037Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:18:32.634997Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:19:32.696146Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:20:32.757221Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:21:32.763815Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:22:32.825474Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:23:32.887129Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:24:32.948929Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:25:33.011047Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:26:33.073136Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:27:33.135149Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:28:33.179990Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:29:33.238942Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:30:33.299554Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:31:33.308219Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:32:33.345398Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:33:33.395704Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:34:33.427733Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:35:33.431536Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:36:33.443827Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:37:33.505390Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:38:33.539840Z | Info | Live bytes: 791.90MB Heap size: 3219.13MB +2024-07-17T09:39:33.541435Z | Info | Live bytes: 802.52MB Heap size: 3219.13MB +2024-07-17T09:40:33.557315Z | Info | Live bytes: 802.54MB Heap size: 3219.13MB +2024-07-17T09:41:33.618780Z | Info | Live bytes: 802.54MB Heap size: 3219.13MB +2024-07-17T09:42:33.659758Z | Info | Live bytes: 822.05MB Heap size: 3219.13MB +2024-07-17T09:43:33.720804Z | Info | Live bytes: 831.32MB Heap size: 3219.13MB +2024-07-17T09:44:33.755666Z | Info | Live bytes: 834.84MB Heap size: 3219.13MB +2024-07-17T09:45:33.787621Z | Info | Live bytes: 834.84MB Heap size: 3219.13MB +2024-07-17T09:46:33.819713Z | Info | Live bytes: 834.84MB Heap size: 3219.13MB +2024-07-17T09:47:33.881001Z | Info | Live bytes: 834.84MB Heap size: 3219.13MB +2024-07-17T09:48:33.890572Z | Info | Live bytes: 834.84MB Heap size: 3219.13MB +2024-07-17T09:49:11.977594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:49:25.401493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:49:26.389881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:49:27.225004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:49:29.533115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:49:30.437148Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:49:31.473060Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T09:49:31.768830Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T09:49:32.285416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:49:33.893031Z | Info | Live bytes: 1203.63MB Heap size: 3219.13MB +2024-07-17T09:50:33.954486Z | Info | Live bytes: 1203.63MB Heap size: 3219.13MB +2024-07-17T09:51:17.948913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:20.481591Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:51:20.578719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:21.667360Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:51:22.166277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:22.615355Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:51:22.775169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:23.548251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:23.850613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:51:24.344793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:24.959882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:25.689782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:26.281353Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:51:33.967075Z | Info | Live bytes: 775.91MB Heap size: 3219.13MB +2024-07-17T09:52:34.008435Z | Info | Live bytes: 776.12MB Heap size: 3219.13MB +2024-07-17T09:53:34.069566Z | Info | Live bytes: 776.12MB Heap size: 3219.13MB +2024-07-17T09:54:04.543626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:05.166328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:05.737657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:07.392777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:09.064800Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:09.203901Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:09.306673Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:09.560415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:10.224982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:10.730941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:11.697608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:12.071912Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:12.202834Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:12.380907Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:12.484772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:12.563495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:12.563519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:12.651302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:13.155382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:13.816992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:14.910934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:18.875888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:21.165103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:25.065857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:25.635640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:32.942975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:34.036058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:34.070078Z | Info | Live bytes: 1871.51MB Heap size: 4053.79MB +2024-07-17T09:54:35.789843Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:36.382269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:38.498916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:39.079574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:58.218925Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:58.345798Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:58.478541Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:54:58.688612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:54:59.422761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:00.058929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:10.774780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:12.012686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:13.131380Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:13.226442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:13.312343Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:13.404477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:13.613531Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:15.534715Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:15.613546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:15.754820Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:15.874258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:16.083994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:16.376857Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:55:16.869876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:55:34.083075Z | Info | Live bytes: 2169.48MB Heap size: 3986.69MB +2024-07-17T09:56:34.139828Z | Info | Live bytes: 2169.48MB Heap size: 3986.69MB +2024-07-17T09:57:34.200417Z | Info | Live bytes: 2169.48MB Heap size: 3986.69MB +2024-07-17T09:58:11.951031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:58:12.197503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:58:12.424182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:13.190020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:13.987847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:14.561383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:15.551482Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:21.459906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:22.253734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:34.207499Z | Info | Live bytes: 781.82MB Heap size: 4160.75MB +2024-07-17T09:58:39.765426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:40.449944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:42.143557Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T09:58:42.355912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:43.354037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:58:43.962589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T09:59:34.254034Z | Info | Live bytes: 874.97MB Heap size: 4160.75MB +2024-07-17T10:00:03.013564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:03.346746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:00:03.422393Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:00:03.566473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:04.094361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:00:04.603408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:05.632645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:07.501752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:08.344835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:09.440013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:10.806988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:13.061776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:00:34.272621Z | Info | Live bytes: 1234.39MB Heap size: 4160.75MB +2024-07-17T10:01:34.328701Z | Info | Live bytes: 1245.19MB Heap size: 4160.75MB +2024-07-17T10:01:42.207195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:01:42.504701Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:01:42.700471Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:01:42.874846Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:01:42.958345Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:01:42.982246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:01:43.036789Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:01:43.148044Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:01:43.540282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:01:44.146480Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:01:45.499461Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:02:34.374578Z | Info | Live bytes: 1409.79MB Heap size: 4160.75MB +2024-07-17T10:03:34.383508Z | Info | Live bytes: 1409.79MB Heap size: 4160.75MB +2024-07-17T10:04:05.410383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:09.019890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:09.699562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:15.483406Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:15.589613Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:15.693240Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:15.808751Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:15.947297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:16.909478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:17.791383Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:17.950316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:17.993612Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:18.741544Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:19.231858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:20.269565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:21.129183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:22.020736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:22.212457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:22.439681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:22.566328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:22.588533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:23.259939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:23.294775Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:04:23.896071Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:25.109625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:26.577674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:30.956108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:31.573838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:32.236433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:34.386167Z | Info | Live bytes: 1175.11MB Heap size: 4172.28MB +2024-07-17T10:04:36.076492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:40.124912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:40.818629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:42.893809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:43.485341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:44.107874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:47.611696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:49.959443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:50.585058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:51.143627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:51.755974Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:04:52.502607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:03.532961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:04.200353Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:05:04.209587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:04.844732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:04.874482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:05:05.606104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:05.683774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:05:05.875807Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:05:06.181459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:08.510895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:08.849391Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:05:09.202545Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:05:09.710813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:05:34.410467Z | Info | Live bytes: 1902.15MB Heap size: 5776.61MB +2024-07-17T10:06:34.471507Z | Info | Live bytes: 1907.90MB Heap size: 5776.61MB +2024-07-17T10:07:34.515645Z | Info | Live bytes: 1907.90MB Heap size: 5776.61MB +2024-07-17T10:08:34.516803Z | Info | Live bytes: 1920.33MB Heap size: 5776.61MB +2024-07-17T10:08:34.898295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:08:35.680748Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:08:35.817325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:08:35.900427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:08:36.091206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:08:37.291875Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:08:37.544719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:08:38.145414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:08:38.779804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:08:42.936241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:08:52.255448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:34.554505Z | Info | Live bytes: 2271.28MB Heap size: 5776.61MB +2024-07-17T10:09:51.462008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:52.091672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:09:52.557921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:53.207631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:53.517221Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:09:54.018420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:54.589708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:55.879544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:56.529177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:57.156937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:58.530008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:09:58.612691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:09:59.847123Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:00.043214Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:10:00.522223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:02.145000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:02.720890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:04.216849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:11.136970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:12.370309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:15.146212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:22.346150Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:10:22.498269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:10:22.739795Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:10:22.824325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:26.407979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:28.419752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:29.080016Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:33.557007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:34.556742Z | Info | Live bytes: 2546.56MB Heap size: 5776.61MB +2024-07-17T10:10:36.984450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:38.161349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:39.689330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:10:39.936689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:40.538179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:41.133099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:45.861688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:49.034567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:51.905047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:53.514031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:56.386469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:10:59.080905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:00.630848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:01.884785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:08.257556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:08.973957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:12.662325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:13.528388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:14.354170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:15.140774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:17.602873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:20.713865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:21.908192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:22.558018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:25.873339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:32.878630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:34.560578Z | Info | Live bytes: 1124.09MB Heap size: 4046.45MB +2024-07-17T10:11:36.051173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:41.441445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:41.998774Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:42.195982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:42.326682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:43.080169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:43.577565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:43.655535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:43.749679Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:43.815055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:44.055274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:44.743300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:45.589589Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:46.154833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:46.726432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:47.415445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:47.971919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:48.687866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:49.287207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:49.913679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:50.800010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:51.471685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:53.404626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:54.259929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:54.515849Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:54.722868Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:55.013745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:55.359928Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:55.514668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:55.581115Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:55.627932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:55.763932Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:56.041961Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:56.207532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:56.259534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:56.777048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:11:57.275886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:11:58.074735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:12:01.198251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:12:28.583271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:12:32.558698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:12:32.664603Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:12:33.002901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:12:34.561900Z | Info | Live bytes: 1464.78MB Heap size: 4046.45MB +2024-07-17T10:12:34.708505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:12:38.241259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:12:39.906628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:12:42.482152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:04.883822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:05.858496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:06.608871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:07.420114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:21.991895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:22.076606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:22.144264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:22.365687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:24.894552Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:25.054572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:25.210673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:25.762983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:26.398020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:31.615412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:31.923508Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:32.092311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:32.654832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:34.027286Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:34.284134Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:34.565160Z | Info | Live bytes: 1341.83MB Heap size: 4046.45MB +2024-07-17T10:13:35.344490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:37.215503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:37.338799Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:37.390779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:37.431159Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:48.691956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:49.095463Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:49.427829Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:49.635972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:49.673128Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:49.749290Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:49.834249Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:49.890790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.032926Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.247961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:50.257930Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.442517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.575776Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.688061Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.772996Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.924694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:50.927982Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:51.177992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:13:51.687147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:13:55.519383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:10.685270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:11.757230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:13.787001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:15.013723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:16.502567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:18.174354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:20.764849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:14:34.572055Z | Info | Live bytes: 1500.69MB Heap size: 4046.45MB +2024-07-17T10:15:23.803791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:15:24.662276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:15:26.088423Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:15:26.413679Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:15:26.936166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:15:34.579900Z | Info | Live bytes: 1733.10MB Heap size: 4046.45MB +2024-07-17T10:15:39.610600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:00.875366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:04.082185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:04.201129Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:04.840719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:05.606776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:06.076053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:06.311341Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:06.553063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:07.473149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:07.542386Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:08.038368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:08.777167Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:09.667425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:10.625769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:11.845335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:12.403936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:13.064522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:13.529801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:14.141547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:14.686014Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:15.625759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:16.621292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:17.649876Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:17.952272Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:18.087258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:18.119187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:18.201048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:18.636781Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:18.690888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:19.043990Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:19.217084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:19.341915Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:19.541596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:20.023081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:20.101204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:20.480543Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:20.512005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:20.751136Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:20.941986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:21.037864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:21.256063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:21.739012Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:21.844114Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:22.045737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:22.235738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:34.588901Z | Info | Live bytes: 1564.48MB Heap size: 4075.81MB +2024-07-17T10:16:38.603440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:38.701532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:39.153804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:41.208644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:42.869554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:43.926596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:46.208617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:46.962783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:48.719793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:49.211307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:49.850677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:50.683420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:51.744344Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:51.963284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:55.406733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:16:56.898202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:16:57.176581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:02.476752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:06.178910Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:06.439717Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:06.749757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:07.297237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:07.932976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:08.613454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:09.271874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:23.553936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:24.149207Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:24.336746Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:24.394749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:24.439560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:25.091863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:25.531654Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:25.599672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:25.660142Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:25.788290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:26.024183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:26.189095Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:17:26.527606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:17:34.593453Z | Info | Live bytes: 1506.73MB Heap size: 4075.81MB +2024-07-17T10:18:21.992460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:23.493302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:24.412043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:25.152945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:25.929046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:26.803024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:27.760039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:28.820220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:29.277736Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:18:34.598421Z | Info | Live bytes: 904.19MB Heap size: 4006.61MB +2024-07-17T10:18:41.148146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:18:42.810483Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:18:43.118214Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:18:43.632903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:19:34.649798Z | Info | Live bytes: 1051.95MB Heap size: 4006.61MB +2024-07-17T10:20:34.710927Z | Info | Live bytes: 1051.95MB Heap size: 4006.61MB +2024-07-17T10:21:34.747683Z | Info | Live bytes: 1051.95MB Heap size: 4006.61MB +2024-07-17T10:22:34.788083Z | Info | Live bytes: 1051.95MB Heap size: 4006.61MB +2024-07-17T10:23:34.822629Z | Info | Live bytes: 1051.95MB Heap size: 4006.61MB +2024-07-17T10:24:27.191024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:34.826822Z | Info | Live bytes: 1117.26MB Heap size: 4006.61MB +2024-07-17T10:24:37.580427Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:24:37.885152Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:24:38.399139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:49.522838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:51.807587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:52.445180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:53.223909Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:55.541444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:56.854233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:57.705130Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:24:57.902622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:58.158504Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:24:58.404461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:24:58.478083Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:24:58.665007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:24:59.605764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:25:00.381438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:25:02.553986Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:25:02.598516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:25:34.859448Z | Info | Live bytes: 784.82MB Heap size: 4006.61MB +2024-07-17T10:26:34.886584Z | Info | Live bytes: 784.82MB Heap size: 4006.61MB +2024-07-17T10:26:57.010009Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:26:57.111209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:26:57.483181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:26:58.334160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:26:58.589472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:26:58.707042Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:26:58.966792Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:26:59.614859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:00.628402Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:00.881247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:00.961340Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:01.126898Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:01.514174Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:02.003341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:02.407594Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:02.587527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:03.475710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:04.551927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:05.134309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:05.928693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:06.592908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:07.615549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:08.203409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:09.008009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:09.574117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:12.204357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:12.756381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:15.335500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:15.945169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:34.897836Z | Info | Live bytes: 1068.56MB Heap size: 4006.61MB +2024-07-17T10:27:37.967992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:39.343376Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:41.232060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:43.796893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:44.643483Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:44.927274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:44.951302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:45.699976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:46.490627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:47.802871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:48.462342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:49.070345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:51.240011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:51.850486Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:52.108892Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:52.728776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:53.423510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:57.635978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:57.775848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:57.937903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:58.069057Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:58.174819Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:58.330576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:27:58.432114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:27:59.022939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:03.530188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:04.085439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:04.890504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:07.639658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:08.368104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:09.144948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:17.417822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:18.026831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:19.068134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:19.665757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:21.164727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:22.055588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:23.745091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:24.974929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:25.687721Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:28:34.907374Z | Info | Live bytes: 1193.56MB Heap size: 4006.61MB +2024-07-17T10:28:43.862739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:46.226241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:47.011092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:47.047600Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:47.203570Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:47.259187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:47.669150Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:47.689687Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:47.755547Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:47.855081Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:48.099979Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:48.252371Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:48.877704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:49.534629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:50.116818Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:50.488813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:50.686077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:50.749099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:50.938837Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:51.248959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:51.318876Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:51.815183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:54.646279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:54.741153Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:55.064630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:55.663949Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:55.720037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:56.006502Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:56.108516Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:56.233452Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:56.318453Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:56.464255Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:56.501872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:56.543761Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:56.632159Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:28:57.128331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:57.750970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:28:58.848941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:29:25.337372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:29:25.563917Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:29:33.117174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:29:33.130082Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:29:33.436157Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:29:33.929021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:29:34.908622Z | Info | Live bytes: 1510.02MB Heap size: 4006.61MB +2024-07-17T10:29:38.686109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:30:34.922128Z | Info | Live bytes: 862.41MB Heap size: 4006.61MB +2024-07-17T10:31:34.982845Z | Info | Live bytes: 862.41MB Heap size: 4006.61MB +2024-07-17T10:32:35.035802Z | Info | Live bytes: 862.41MB Heap size: 4006.61MB +2024-07-17T10:33:28.764494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:29.897128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:30.534029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:32.561842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:33:32.667482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:33:32.870549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:33.513433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:34.095063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:35.037937Z | Info | Live bytes: 998.39MB Heap size: 4006.61MB +2024-07-17T10:33:38.651232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:41.933481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:33:42.488582Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:33:42.963638Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:34:32.447573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:34:35.041407Z | Info | Live bytes: 1270.53MB Heap size: 4006.61MB +2024-07-17T10:34:35.531219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:34:36.086068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:34:36.679673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:34:39.243008Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:34:39.319838Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:34:39.473209Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:34:39.500338Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:34:39.812978Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:34:39.916540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:34:40.007325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:34:40.315142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:35:35.091963Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:36:35.153573Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:37:35.214801Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:38:35.276054Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:39:35.337025Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:40:35.380958Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:41:35.442429Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:42:35.504181Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:43:35.565903Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:44:35.616282Z | Info | Live bytes: 1408.65MB Heap size: 4006.61MB +2024-07-17T10:44:58.153193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:44:59.177271Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:44:59.589227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:00.356024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:00.960103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:02.019479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:02.074489Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:02.173958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:02.395244Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:02.570435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:02.892620Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:03.388493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:04.061144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:05.228759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:05.325317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:05.447990Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:05.547121Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:05.620608Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:05.955899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:13.932977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:14.735191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:15.349103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:35.636740Z | Info | Live bytes: 1048.44MB Heap size: 4006.61MB +2024-07-17T10:45:38.438656Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:38.507771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:38.661134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:39.229075Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:39.560346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:39.725463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:40.109968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:40.207976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:40.582187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:41.095437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:41.145018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:41.334968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:41.487518Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:41.730056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:41.804145Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:41.833851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:41.974638Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:42.103895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:42.261306Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:42.476819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:42.766284Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:43.240122Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:43.259161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:43.593910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:43.964113Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:44.028597Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:44.092654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:44.160187Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:44.300238Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:44.442412Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:44.644885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:44.750619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:44.961768Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:45.167123Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:45.245191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:45.305477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:45.410960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:45.619389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:45.709182Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:45.809608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:45.838230Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:46.426169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:47.014161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:48.971366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:54.092430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:54.352207Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:54.837039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:54.837178Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:45:55.399135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:45:59.561326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:02.439047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:03.155570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:03.784825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:03.931480Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:03.992367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:04.706246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:04.805496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:05.080553Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:05.307198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:05.639884Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:05.776584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:06.140414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:06.780093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:09.819045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:10.147956Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:10.335276Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:10.458559Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:10.629117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:10.835242Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:11.335919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:12.487057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:13.393999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:13.955942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:14.639583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:15.243549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:15.901275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:16.764481Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:17.392190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:18.445057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:18.761296Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:19.150387Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:19.326110Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:19.509334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:19.822176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:20.515549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:20.605026Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:21.108051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:22.061328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:22.702025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:24.262005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:27.362171Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:27.525305Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:27.650236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:27.681499Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:27.752239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:27.826802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:27.926645Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:28.165141Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:28.251195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:28.258902Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:28.522763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:28.617749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:28.722595Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:28.871884Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:28.996782Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:29.018938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:32.427532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:35.640470Z | Info | Live bytes: 1155.66MB Heap size: 4351.59MB +2024-07-17T10:46:37.059683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:39.440052Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:44.227668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:44.426140Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:44.603506Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:44.893949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:46.579261Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:46:46.657269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:47.662822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:48.241225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:48.893992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:46:51.346046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:01.353707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:03.344292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:17.634601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:29.769521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:30.536776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:30.540542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:30.704241Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:31.197538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:31.910533Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:32.090179Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:32.181193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:32.411720Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:32.419888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:32.551323Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:32.648759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:32.886001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:33.015664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:33.053790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:33.213872Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:33.394872Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:33.553055Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:33.713678Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:33.728107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:34.072193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:34.243206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:34.327502Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:34.534815Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:34.580318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:35.103346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:35.245443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:35.345407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:35.606729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:35.641353Z | Info | Live bytes: 1240.95MB Heap size: 4224.71MB +2024-07-17T10:47:36.218177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:36.417437Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:36.571958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:36.906220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:37.196843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:37.690830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:38.251812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:39.558796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:41.045529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:41.623581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:42.481273Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:42.499501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:42.666748Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:42.741461Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:43.159352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:44.201625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:44.798914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:44.962149Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:45.446074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:46.060515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:49.998313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:52.069320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:52.397963Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:52.669442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:53.228195Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:53.245766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:53.411688Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:53.529324Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:47:53.908887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:47:59.852606Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:48:00.345549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:48:02.923578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T10:48:03.238105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:48:03.548702Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T10:48:35.669303Z | Info | Live bytes: 1499.28MB Heap size: 4224.71MB +2024-07-17T10:49:35.730547Z | Info | Live bytes: 1499.28MB Heap size: 4224.71MB +2024-07-17T10:50:19.645314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:50:35.742683Z | Info | Live bytes: 968.05MB Heap size: 4224.71MB +2024-07-17T10:51:35.755796Z | Info | Live bytes: 968.05MB Heap size: 4224.71MB +2024-07-17T10:51:54.438839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T10:52:35.793638Z | Info | Live bytes: 1197.53MB Heap size: 4224.71MB +2024-07-17T10:53:35.810560Z | Info | Live bytes: 1197.53MB Heap size: 4224.71MB +2024-07-17T10:54:35.872120Z | Info | Live bytes: 1197.53MB Heap size: 4224.71MB +2024-07-17T10:55:35.933538Z | Info | Live bytes: 1197.53MB Heap size: 4224.71MB +2024-07-17T10:56:35.961546Z | Info | Live bytes: 1197.53MB Heap size: 4224.71MB +2024-07-17T10:57:36.004655Z | Info | Live bytes: 1197.53MB Heap size: 4224.71MB +2024-07-17T10:58:36.064411Z | Info | Live bytes: 1197.53MB Heap size: 4224.71MB +2024-07-17T10:59:36.094039Z | Info | Live bytes: 1165.72MB Heap size: 4224.71MB +2024-07-17T11:00:36.097059Z | Info | Live bytes: 1431.30MB Heap size: 4224.71MB +2024-07-17T11:01:36.158235Z | Info | Live bytes: 1431.30MB Heap size: 4224.71MB +2024-07-17T11:02:36.164981Z | Info | Live bytes: 1431.30MB Heap size: 4224.71MB +2024-07-17T11:03:36.225428Z | Info | Live bytes: 1431.30MB Heap size: 4224.71MB +2024-07-17T11:04:36.286220Z | Info | Live bytes: 1431.30MB Heap size: 4224.71MB +2024-07-17T11:04:52.233559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:04:56.164788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:04:56.894624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:00.360724Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:00.923275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:01.574576Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:07.857871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:09.200473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:10.051357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:13.927112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:15.760145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:19.268112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:19.339205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:21.424887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:22.536107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:23.006418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:23.733689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:24.013262Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:24.497102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:25.794369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:26.020154Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:26.500919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:27.157609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:27.211823Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:27.831419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:28.060473Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:31.481200Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:31.957880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:32.054466Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:32.535853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:32.579880Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:32.982988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:33.353711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:36.290325Z | Info | Live bytes: 1558.02MB Heap size: 4224.71MB +2024-07-17T11:05:37.344454Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:37.351164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:40.405450Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:40.712765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:41.785246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:05:55.896090Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:05:56.352617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:00.546875Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:06:01.032501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:06.380120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:08.360599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:11.700410Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:06:12.080659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-17T11:06:12.179725Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:25.104472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:25.710933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:26.262090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:26.856906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:28.550984Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T11:06:28.856446Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T11:06:29.374876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:34.072063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:34.339271Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T11:06:34.682371Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" ] +2024-07-17T11:06:35.188654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:06:36.291688Z | Info | Live bytes: 1612.92MB Heap size: 4224.71MB +2024-07-17T11:07:36.320304Z | Info | Live bytes: 1615.68MB Heap size: 4224.71MB +2024-07-17T11:08:36.376778Z | Info | Live bytes: 1619.86MB Heap size: 4224.71MB +2024-07-17T11:09:36.437488Z | Info | Live bytes: 1619.86MB Heap size: 4224.71MB +2024-07-17T11:09:38.435360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:09:38.438338Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:09:49.557783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:09:49.567421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:10:33.269050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:10:36.440889Z | Info | Live bytes: 1333.16MB Heap size: 4224.71MB +2024-07-17T11:10:55.423370Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:10:56.274407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:11:36.462738Z | Info | Live bytes: 1613.01MB Heap size: 4224.71MB +2024-07-17T11:11:47.653299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T11:12:36.507870Z | Info | Live bytes: 1682.35MB Heap size: 4224.71MB +2024-07-17T11:13:36.549246Z | Info | Live bytes: 1682.35MB Heap size: 4224.71MB +2024-07-17T11:14:36.608045Z | Info | Live bytes: 1682.35MB Heap size: 4224.71MB +2024-07-17T11:15:36.668734Z | Info | Live bytes: 1682.35MB Heap size: 4224.71MB +2024-07-17T11:16:36.699835Z | Info | Live bytes: 1682.35MB Heap size: 4224.71MB +2024-07-17T11:17:36.760428Z | Info | Live bytes: 1682.35MB Heap size: 4224.71MB +2024-07-17T11:18:36.785397Z | Info | Live bytes: 1682.35MB Heap size: 4224.71MB +2024-07-17T11:19:36.787992Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:20:36.848470Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:21:36.908391Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:22:36.968512Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:23:37.028383Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:24:37.088396Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:25:37.143249Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:26:37.203999Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:27:37.230983Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:28:37.291460Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:29:37.356361Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:30:37.370921Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:31:37.422624Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:32:37.482973Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:33:37.489499Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:34:37.547104Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:35:37.607517Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:36:37.668040Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:37:37.700409Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:38:37.728605Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:39:37.788379Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:40:37.791804Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:41:37.819226Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:42:37.879483Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:43:37.939886Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:44:38.000368Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:45:38.061083Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:46:38.122414Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:47:38.163671Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:48:38.224812Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:49:38.285966Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:50:38.347571Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:51:38.408920Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:52:38.470192Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:53:38.531554Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:54:38.592747Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:55:38.653944Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:56:38.715162Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:57:38.776173Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:58:38.836921Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T11:59:38.843733Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:00:38.905162Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:01:38.966554Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:02:39.027891Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:03:39.036427Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:04:39.097155Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:05:39.157346Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:06:39.217534Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:07:39.278455Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:08:39.338500Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:09:39.371439Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:10:39.431517Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:11:39.491433Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:12:39.531383Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:13:39.578016Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:14:39.589685Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:15:39.649406Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:16:39.709608Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:17:39.770479Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:18:39.777571Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:19:39.781116Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:20:39.835599Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:21:39.896068Z | Info | Live bytes: 1691.39MB Heap size: 4224.71MB +2024-07-17T12:22:03.039286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:22:39.925414Z | Info | Live bytes: 1000.58MB Heap size: 4224.71MB +2024-07-17T12:23:39.985406Z | Info | Live bytes: 1000.58MB Heap size: 4224.71MB +2024-07-17T12:24:14.856192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:24:29.994519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:24:38.967181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:24:39.987005Z | Info | Live bytes: 1315.82MB Heap size: 4224.71MB +2024-07-17T12:25:40.001999Z | Info | Live bytes: 1483.87MB Heap size: 4224.71MB +2024-07-17T12:26:40.062712Z | Info | Live bytes: 1483.87MB Heap size: 4224.71MB +2024-07-17T12:26:42.337524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:26:45.822044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:27:00.703417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:27:07.366038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:27:40.085489Z | Info | Live bytes: 1515.54MB Heap size: 4224.71MB +2024-07-17T12:28:40.108496Z | Info | Live bytes: 1515.54MB Heap size: 4224.71MB +2024-07-17T12:29:40.169244Z | Info | Live bytes: 1515.54MB Heap size: 4224.71MB +2024-07-17T12:30:36.488793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:30:40.169934Z | Info | Live bytes: 922.81MB Heap size: 4224.71MB +2024-07-17T12:31:40.197123Z | Info | Live bytes: 1139.95MB Heap size: 4224.71MB +2024-07-17T12:31:43.364771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:32:40.242490Z | Info | Live bytes: 1525.14MB Heap size: 4224.71MB +2024-07-17T12:33:11.578357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T12:33:40.260108Z | Info | Live bytes: 999.41MB Heap size: 4224.71MB +2024-07-17T12:34:40.318599Z | Info | Live bytes: 999.41MB Heap size: 4224.71MB +2024-07-17T12:35:40.324549Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:36:40.375997Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:37:40.437013Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:38:40.498467Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:39:40.560100Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:40:40.620712Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:41:40.681675Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:42:40.742218Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:43:40.803123Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:44:40.864567Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:45:40.925918Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:46:40.951450Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:47:41.004216Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:48:41.018042Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:49:41.079083Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:50:41.140334Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:51:41.201554Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:52:41.262799Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:53:41.301527Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:54:41.316600Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:55:41.377881Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:56:41.439236Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:57:41.500519Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:58:41.561761Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T12:59:41.563596Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:00:41.624525Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:01:41.685745Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:02:41.746959Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:03:41.808467Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:04:41.869848Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:05:41.930843Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:06:41.991559Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:07:42.052656Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:08:42.113660Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:09:42.154444Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:10:42.215767Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:11:42.274828Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:12:42.335451Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:13:42.396368Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:14:42.400588Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:15:42.461462Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:16:42.522688Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:17:42.573334Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:18:42.633454Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:19:42.694128Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:20:42.755316Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:21:42.772618Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:22:42.833393Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:23:42.848845Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:24:42.884025Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:25:42.944766Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:26:43.005560Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:27:43.066422Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:28:43.127156Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:29:43.187578Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:30:43.248233Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:31:43.309087Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:32:43.369933Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:33:43.430387Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:34:43.456552Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:35:43.516650Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:36:43.577403Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:37:43.638376Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:38:43.699541Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:39:43.759478Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:40:43.820375Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:41:43.881413Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:42:43.941470Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:43:44.002327Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:44:44.059551Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:45:44.120563Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:46:44.181552Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:47:44.233839Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:48:44.244748Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:49:44.305706Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:50:44.366767Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:51:44.427190Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:52:44.487345Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:53:44.494320Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:54:44.554394Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:55:44.584500Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:56:44.645434Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:57:44.706947Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:58:44.757335Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T13:59:44.818467Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:00:44.879580Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:01:44.940618Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:02:44.955757Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:03:45.017202Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:04:45.078495Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:05:45.139949Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:06:45.190751Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:07:45.229492Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:08:45.290199Z | Info | Live bytes: 1233.19MB Heap size: 4224.71MB +2024-07-17T14:09:21.824984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T14:09:44.606924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T14:09:45.291529Z | Info | Live bytes: 1263.15MB Heap size: 4224.71MB +2024-07-17T14:10:23.881789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T14:10:45.296015Z | Info | Live bytes: 1322.33MB Heap size: 4224.71MB +2024-07-17T14:11:08.771097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T14:11:12.369585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T14:11:17.885036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-17T14:11:45.318478Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:12:45.378316Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:13:45.438470Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:14:45.478615Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:15:45.538618Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:16:45.599434Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:17:45.602168Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:18:45.663312Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:19:45.667753Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:20:45.698081Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:21:45.758871Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:22:45.819779Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:23:45.879399Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:24:45.918499Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:25:45.978432Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:26:46.038410Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:27:46.098594Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:28:46.159466Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:29:46.220451Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:30:46.281421Z | Info | Live bytes: 1380.38MB Heap size: 4224.71MB +2024-07-17T14:31:14.451135Z | Info | LSP: received shutdown +2024-07-17T14:31:14.455527Z | Error | Got EOF +2024-07-18 06:09:07.6330000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-18 06:09:07.6370000 [client] INFO Finding haskell-language-server +2024-07-18 06:09:07.6390000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:07.6390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:07.6460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-18 06:09:07.8040000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:07.8040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:07.8090000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-18 06:09:07.9400000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:07.9400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:07.9450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-18 06:09:08.0510000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:08.0510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:08.0560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-18 06:09:08.1760000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:08.1760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:08.1800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-18 06:09:08.1950000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:08.1960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:08.2020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-18 06:09:08.2170000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:08.2170000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:08.2230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-18 06:09:08.2430000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-18 06:09:08.2880000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:08.2880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:08.2930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-18 06:09:08.3980000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-18 06:09:08.3980000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-18 06:09:17.3320000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-18 06:09:17.4500000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-18 06:09:17.4500000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:17.4500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:17.4540000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-18 06:09:17.5280000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:17.5280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:17.5310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-18 06:09:17.5460000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:17.5460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:17.5500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-18 06:09:17.5630000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:17.5640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:17.5680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-18 06:09:17.5810000 [client] INFO Checking for ghcup installation +2024-07-18 06:09:17.5810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-18 06:09:17.5860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-18 06:09:17.6810000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-18 06:09:17.6810000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-18 06:09:17.6810000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-18 06:09:17.6810000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-18 06:09:17.6810000 [client] INFO server environment variables: +2024-07-18 06:09:17.6810000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-18 06:09:17.6820000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-18 06:09:17.6820000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-18 06:09:17.6830000 [client] INFO Starting language server +2024-07-18T06:09:26.535469Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-18T06:09:26.536434Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-18T06:09:26.536650Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T06:09:26.538722Z | Info | Logging heap statistics every 60.00s +2024-07-18T06:09:26.546278Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T06:09:26.546707Z | Info | Starting server +2024-07-18T06:09:26.548666Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-18T06:09:26.642600Z | Info | Started LSP server in 0.10s +2024-07-18T06:09:27.846959Z | Info | Cradle path: cardano-api/internal/Cardano/Api/IPC/Monad.hs +2024-07-18T06:09:27.847903Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-18T06:09:28.400306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T06:09:29.299651Z | Info | Load cabal cradle using single file +2024-07-18T06:09:30.155526Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT9043-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-18T06:09:37.140149Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-c875534007e32f9c29d109be7ba71e4921e24ed2 +2024-07-18T06:09:37.145644Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-18T06:10:26.543413Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:11:26.550696Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:12:26.566497Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:13:26.612409Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:14:26.668444Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:15:26.693463Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:16:26.708566Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:17:26.740500Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:18:26.758215Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:19:26.818754Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:20:26.859681Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:21:26.884353Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:22:26.944363Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:23:26.946568Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:24:26.964438Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:25:27.025128Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:26:27.085593Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:27:27.145318Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:28:27.204448Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:29:27.265086Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:30:27.284420Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:31:27.286308Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:32:27.346955Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:33:27.380682Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:34:27.412462Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:35:27.473149Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:36:27.514953Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:37:27.572525Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:38:27.593514Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:39:27.653957Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:40:27.714649Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:41:27.740447Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:42:27.801167Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:43:27.852469Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:44:27.857383Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:45:27.870135Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:46:27.924414Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:47:27.985163Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:48:28.001149Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:49:28.020440Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:50:28.036520Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:51:28.084402Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:52:28.116484Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:53:28.177097Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:54:28.180415Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T06:55:28.224159Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:23:00.408857Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:24:00.467524Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:25:00.523501Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:26:00.583404Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:27:00.643934Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:28:00.704536Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:29:00.742495Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:30:00.803091Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:31:00.837494Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:32:00.883592Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:33:00.885908Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:34:00.946589Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:35:01.007155Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:36:01.067739Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:37:01.128352Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:38:01.188798Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:39:01.249493Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:40:01.307470Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:41:01.355576Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:42:01.415365Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:43:01.450946Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:44:01.511572Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:45:01.572388Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:46:01.587459Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:47:01.629884Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:48:01.651545Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:49:01.712200Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:50:01.735584Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:51:01.796088Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:52:01.856355Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:53:01.916499Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:54:01.977344Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:55:02.037930Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:56:02.098370Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:57:02.131539Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:58:02.192125Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T07:59:02.193405Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:00:02.251682Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:01:02.283578Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:02:02.307494Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:03:02.333906Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:04:02.394582Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:05:02.454372Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:06:02.514320Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:07:02.574974Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:08:02.605328Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:09:02.665381Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:10:02.715828Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:11:02.733910Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:12:02.734828Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:13:02.791083Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:14:02.851669Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:15:02.899490Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:16:02.947451Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:17:02.987842Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:18:03.000349Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:19:03.060870Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:20:03.097262Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:21:03.148840Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:22:03.209355Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:23:03.226452Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:24:03.286935Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:25:03.347407Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:26:03.407273Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:27:03.446517Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:28:03.448559Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:29:03.474463Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:30:03.478598Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:31:03.504397Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:32:03.520583Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:33:03.539526Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:34:03.596108Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:35:03.642386Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:36:03.659521Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:37:03.719980Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:38:03.780560Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:39:03.827538Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:40:03.870662Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:41:03.920397Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:42:03.936835Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:43:03.993992Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:44:04.019569Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:45:04.027543Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:46:04.087321Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:47:04.128839Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:48:04.189307Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:49:04.221454Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:50:04.282135Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T08:51:04.293465Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T09:54:17.642355Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T09:55:17.665742Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T09:56:17.726318Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T09:57:17.778407Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T09:58:17.839030Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T09:59:17.899645Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:00:17.960228Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:01:18.020831Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:02:18.081379Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:03:18.131585Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:04:18.192184Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:05:18.202405Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:06:18.234341Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:07:18.295007Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:08:18.322268Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:09:18.347417Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:10:18.407935Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:11:18.468158Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:12:18.480790Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:13:18.541406Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:14:18.583506Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:15:18.636421Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:16:18.677072Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:17:18.722396Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:18:18.758301Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:19:18.802385Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:20:18.840613Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:21:18.841533Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:22:18.901218Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:23:18.961890Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:24:19.022298Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:25:19.083057Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:26:19.098951Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:27:19.122424Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:28:19.155297Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:29:19.215961Z | Info | Live bytes: 490.50MB Heap size: 1801.45MB +2024-07-18T10:30:19.218416Z | Info | Live bytes: 585.94MB Heap size: 2219.84MB +2024-07-18T10:30:34.039077Z | Info | LSP: received shutdown +2024-07-18T10:30:34.041260Z | Error | Got EOF +2024-07-18T10:40:43.119961Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-18T10:40:43.130309Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-18T10:40:43.130823Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T10:40:43.133402Z | Info | Logging heap statistics every 60.00s +2024-07-18T10:40:43.140931Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T10:40:43.141401Z | Info | Starting server +2024-07-18T10:40:43.143305Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-18T10:40:43.177832Z | Info | Started LSP server in 0.04s +2024-07-18T10:40:48.120675Z | Info | LSP: received shutdown +2024-07-18T10:40:48.121544Z | Info | Reactor thread stopped +2024-07-18T10:40:48.129658Z | Error | Got EOF +2024-07-18T10:42:17.005201Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-18T10:42:17.006165Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-18T10:42:17.006392Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T10:42:17.009060Z | Info | Logging heap statistics every 60.00s +2024-07-18T10:42:17.015756Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T10:42:17.016268Z | Info | Starting server +2024-07-18T10:42:17.018066Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-18T10:42:17.061687Z | Info | Started LSP server in 0.05s +2024-07-18T10:42:18.241564Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:42:18.242723Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-18T10:42:18.739635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:42:18.739697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:42:19.538361Z | Info | Load cabal cradle using single file +2024-07-18T10:42:20.367407Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT90965-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-18T10:42:27.169397Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-18T10:42:27.175219Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-18T10:42:29.056222Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-18T10:43:05.365716Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:05.366036Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:05.855682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:05.855737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:06.385715Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:43:06.665708Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:06.666077Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:07.155936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:07.156003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:07.325380Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:43:08.985797Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:08.986203Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:09.475956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:09.476002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:10.205418Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:43:11.095105Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:11.095360Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:11.584944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:11.585115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:13.061498Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:43:14.717838Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:14.718227Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:14.833397Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:14.833604Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:14.948931Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:14.949362Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:15.208379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:15.208515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:15.730711Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:15.730925Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:16.123236Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:16.123583Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:16.220864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:16.220992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:17.011183Z | Info | Live bytes: 732.55MB Heap size: 1938.82MB +2024-07-18T10:43:17.048053Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:17.048382Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:17.138210Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:17.138642Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:17.221339Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:17.221817Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:17.538207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:17.538208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:17.727568Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:43:31.884859Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:31.885140Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:32.378472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:32.378621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:33.017006Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:33.017239Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:33.506451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:33.506451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:34.860590Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:43:38.949239Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:38.949619Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:43:39.439115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:39.439169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:43:40.474182Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:44:05.684427Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:44:05.684647Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:44:06.174878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:44:06.174932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:44:07.419690Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:44:17.016083Z | Info | Live bytes: 813.20MB Heap size: 2088.76MB +2024-07-18T10:45:17.076404Z | Info | Live bytes: 813.20MB Heap size: 2088.76MB +2024-07-18T10:46:17.136764Z | Info | Live bytes: 813.20MB Heap size: 2088.76MB +2024-07-18T10:46:49.080066Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:49.080333Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:49.456241Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:49.456614Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:49.570326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:49.570383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:52.323674Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:52.323961Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:52.814053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:52.814134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:53.947380Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:53.947719Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:54.437514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:54.437700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:54.696966Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:54.697184Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:55.187228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:55.187327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:56.007067Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:56.007415Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:56.497274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:56.497447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:46:59.685447Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:46:59.685917Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:00.175255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:00.175257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:01.528303Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:01.528667Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:01.962926Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:01.963166Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:02.018275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:02.018332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:03.408202Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:03.408607Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:03.826363Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:03.826670Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:03.868744Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:03.869089Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:03.898443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:03.898443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:03.940192Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:03.940448Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.167562Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.167750Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.393074Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.393299Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.430363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:04.430412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:04.518602Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.519077Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.650377Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.650666Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.817563Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:04.817736Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.008685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:05.008813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:05.189090Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.189411Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.323629Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.323850Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.380084Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.380429Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.568234Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.568415Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.679039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:05.679066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:05.727686Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:05.727927Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.070897Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.071294Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.179606Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.179889Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.228183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:06.228283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:06.291598Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.291885Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.383624Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.383947Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:06.783817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:06.783822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:06.787671Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:47:13.646695Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:13.647123Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:14.136881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:14.136955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:14.181303Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:14.181581Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:14.671577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:14.671604Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:17.140457Z | Info | Live bytes: 579.72MB Heap size: 2485.13MB +2024-07-18T10:47:19.603858Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:19.604313Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:20.093890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:20.093956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:20.623040Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:20.623291Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:21.113216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:21.113286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:21.330194Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:21.330842Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:21.820441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:21.820441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:22.272159Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:47:22.446839Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:22.447119Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:22.936445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:22.936505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:23.176899Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:23.177090Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:23.667310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:23.667361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:27.704994Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:27.705310Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:27.795935Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:27.796327Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:27.875180Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:27.875426Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.058417Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.058716Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.147702Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.148056Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.195102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:28.195196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:28.226832Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.227033Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.354680Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.355066Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.449920Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.450162Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.527268Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.527706Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:28.717265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:28.717297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:28.988749Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:47:29.237307Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:29.237634Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:29.727980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:29.728092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:34.431923Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:34.432142Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:34.922162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:34.922172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:35.138437Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:47:43.813140Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:43.813575Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:44.303454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:44.303463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:45.789597Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:45.789969Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:46.280172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:46.280249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:56.577349Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:56.577590Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:57.067443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:57.067465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:57.767294Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:57.767558Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:47:58.257605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:58.257682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:47:59.245943Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:48:08.348980Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:08.349339Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:08.615246Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:08.615490Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:08.747427Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:08.747634Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:08.839383Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:08.839381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:10.763907Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:48:10.809222Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:10.809635Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:11.299363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:11.299512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:17.144684Z | Info | Live bytes: 578.17MB Heap size: 2485.13MB +2024-07-18T10:48:19.216146Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.216393Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.375295Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.375684Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.526342Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.527180Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.609162Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.609386Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:19.705873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:19.705987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:20.007249Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.007630Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.086908Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.087225Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.207177Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.207515Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.357239Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.357419Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.459777Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.460207Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.492597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:20.492604Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:20.510643Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.511098Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.599637Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.599948Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.738391Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.738692Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.907058Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.907418Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.999096Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:20.999311Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:21.006259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:21.006585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:21.127439Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:21.127785Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:21.468262Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:48:21.617451Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:21.617580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:48.565540Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:48.565930Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:49.055550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:49.055579Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:49.389786Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:49.390164Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:49.880463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:49.880675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:50.399075Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:50.399400Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:50.889144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:50.889206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:51.253958Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:51.254234Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:51.496597Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:51.497177Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:51.744660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:51.744717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:52.683573Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:48:52.744648Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:52.744893Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:48:53.236979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:48:53.237083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:17.163159Z | Info | Live bytes: 581.98MB Heap size: 2485.13MB +2024-07-18T10:49:35.022240Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:35.022508Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:35.512873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:35.512942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:35.695732Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:35.696037Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:36.073711Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:36.073932Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:36.185863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:36.185869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:36.787918Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:36.788296Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:36.942212Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:36.942480Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:37.278061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:37.278238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:37.869401Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:37.869713Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:38.367035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:38.367035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:40.844928Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:40.845237Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:40.955746Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:40.955940Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:41.070362Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:41.070562Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:49:41.334380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:41.334530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:49:41.472350Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:50:02.255412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:02.255442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:17.179359Z | Info | Live bytes: 582.18MB Heap size: 2485.13MB +2024-07-18T10:50:21.767874Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:21.768118Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:22.227127Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:22.227519Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:22.258004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:22.258097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:23.129782Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:23.130165Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:23.489446Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T10:50:23.619608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:23.619617Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:42.393480Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.393793Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.593514Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.593762Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.720058Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.720542Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.868517Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.868717Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.883515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:42.883718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:42.994287Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:42.994523Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.077734Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.078051Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.173825Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.174241Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.445160Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.445404Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.484428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:43.484489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:43.560941Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.561324Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.695388Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.695731Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.831471Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.831858Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.903146Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.903513Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.975732Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:43.976105Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.051324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:44.051441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:44.087810Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.088151Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.215699Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.215995Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.325311Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.325673Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.428946Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.429270Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.578180Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:44.578233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:44.624932Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.625229Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.722300Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.722815Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.775390Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.775579Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.879206Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.879473Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.948265Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:44.948633Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.024741Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.025069Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.083924Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.084169Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.115119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:45.115188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:45.300212Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.300534Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.429050Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.429233Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.587656Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.587842Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.709504Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.709799Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.790472Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:45.790551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:45.801977Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.802267Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.885976Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:45.886331Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.097541Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.097772Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.291880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:46.291905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:46.309531Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.309901Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.398726Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.399057Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.427662Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.427862Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:46.799709Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:46.799808Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:48.932747Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:48.933263Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.112253Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.112537Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.406704Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.407071Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.422158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:49.422216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:49.505127Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.505620Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.668900Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.669151Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.891985Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.892199Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.936770Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.937180Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:49.994678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:49.994721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:50.082601Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.082995Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.199231Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.199526Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.275465Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.275767Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.572961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:50.573311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:50.574865Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.575048Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.709074Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.709312Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.860640Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:50.860924Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.003695Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.003977Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.065160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:51.065294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:51.114474Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.114705Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.240242Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.240511Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.352427Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.352757Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.455470Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.455775Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:51.604623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:51.604678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:52.008711Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:52.009095Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:52.174711Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:52.175013Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:52.338976Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:52.339351Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:52.498742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:52.498953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:53.239940Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.240416Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.331845Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.332167Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.420266Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.420497Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.483363Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.483843Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.542211Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.542509Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.660986Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.661308Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.729918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:53.729991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:53.880883Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:53.881159Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.069485Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.069818Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.188294Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.188509Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.311432Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.311727Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.370848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:54.370901Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:54.407678Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.407865Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.535463Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.535782Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.822689Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.822906Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:54.897835Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:54.897897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:55.491833Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:55.492059Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:55.981921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:55.981983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:56.034156Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:56.034690Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:56.523925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:56.524069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:57.325997Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.326337Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.423437Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.423845Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.536307Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.536760Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.748380Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.748679Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.816090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:57.816197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:57.954535Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:57.954742Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.043511Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.043763Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.123791Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.124117Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.256598Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.256921Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.318960Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.319330Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.444895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:58.445073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:58.468487Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.468718Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.958927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:58.958953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:58.980145Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:58.980514Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:59.086871Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:59.087084Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:59.190282Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:59.190605Z | Warning | VFS: don't know about URI file:///home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:50:59.469986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:50:59.470037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:51:17.180349Z | Info | Live bytes: 585.88MB Heap size: 2485.13MB +2024-07-18T10:52:04.724092Z | Info | LSP: received shutdown +2024-07-18T10:52:04.725835Z | Error | Got EOF +2024-07-18T10:52:16.665792Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-18T10:52:16.666708Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-18T10:52:16.666940Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T10:52:16.670377Z | Info | Logging heap statistics every 60.00s +2024-07-18T10:52:16.677391Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T10:52:16.677766Z | Info | Starting server +2024-07-18T10:52:16.679587Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-18T10:52:16.737556Z | Info | Started LSP server in 0.06s +2024-07-18T10:52:17.922620Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-18T10:52:17.923216Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-18T10:52:18.466454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:52:19.333358Z | Info | Load cabal cradle using single file +2024-07-18T10:52:20.261711Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT97776-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-18T10:52:27.361632Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-91ce7db861ce9f8a5fa5cdd35181cbff88842a76 +2024-07-18T10:52:27.366315Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-18T10:52:40.253549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:53:05.878619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:53:16.694174Z | Info | Live bytes: 594.99MB Heap size: 2119.17MB +2024-07-18T10:54:16.706437Z | Info | Live bytes: 594.99MB Heap size: 2119.17MB +2024-07-18T10:55:13.034097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:13.536206Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T10:55:16.709964Z | Info | Live bytes: 613.05MB Heap size: 2119.17MB +2024-07-18T10:55:19.741197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:27.785202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:29.538213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:30.746378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:31.090869Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T10:55:45.746262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:46.323989Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T10:55:50.271309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:53.972299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:55:58.682782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:00.283914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:01.135708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:01.931789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:02.461938Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:06.558714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:11.310684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:12.624939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:13.644194Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-18T10:56:16.711128Z | Info | Live bytes: 734.89MB Heap size: 2119.17MB +2024-07-18T10:56:19.504778Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-18T10:56:19.698778Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:56:28.428768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:57:16.759527Z | Info | Live bytes: 752.57MB Heap size: 2119.17MB +2024-07-18T10:58:16.776226Z | Info | Live bytes: 752.57MB Heap size: 2119.17MB +2024-07-18T10:59:16.836875Z | Info | Live bytes: 752.57MB Heap size: 2119.17MB +2024-07-18T10:59:21.027735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T10:59:24.372108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:00:16.847976Z | Info | Live bytes: 777.14MB Heap size: 2119.17MB +2024-07-18T11:01:13.731964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:14.283667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:15.547722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:15.856668Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:15.921125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:16.009306Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:16.470688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:16.492933Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:16.848693Z | Info | Live bytes: 777.13MB Heap size: 2119.17MB +2024-07-18T11:01:17.142038Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:17.566426Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:17.600599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:17.739692Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:17.885514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:18.200500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:19.206131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:20.509495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:21.172433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:34.144544Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:34.743632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:35.370142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:35.899259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:01:35.959784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:36.552516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:37.319173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:38.364379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:39.387313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:48.528367Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:49.055108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:01:53.395264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:02:06.265151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:02:10.467234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:02:11.669834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:02:12.647327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:02:13.176964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:02:15.102503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:02:16.851321Z | Info | Live bytes: 833.01MB Heap size: 2235.56MB +2024-07-18T11:03:16.909377Z | Info | Live bytes: 833.01MB Heap size: 2235.56MB +2024-07-18T11:04:16.931239Z | Info | Live bytes: 833.01MB Heap size: 2235.56MB +2024-07-18T11:05:16.946252Z | Info | Live bytes: 833.01MB Heap size: 2235.56MB +2024-07-18T11:05:57.162610Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:05:57.372511Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:05:59.481657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:00.871678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:16.951779Z | Info | Live bytes: 842.74MB Heap size: 2235.56MB +2024-07-18T11:06:18.445005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:27.906841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:33.233094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:34.127769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:34.952991Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:06:40.073186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:55.496307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:56.511425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:57.322302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:57.961764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:58.520043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:59.032568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:06:59.637890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:00.135381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:00.681381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:01.561968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:02.123047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:02.663849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:03.901208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:16.963301Z | Info | Live bytes: 939.96MB Heap size: 2301.62MB +2024-07-18T11:07:17.842357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:19.292972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:27.044727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:27.647249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:28.226825Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:30.343205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:31.709707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:07:32.581515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:06.207519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:09.489491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:10.008213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:10.473549Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:16.968266Z | Info | Live bytes: 968.27MB Heap size: 2379.22MB +2024-07-18T11:08:19.937035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:20.655830Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:22.312614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:22.604610Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:36.798509Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:36.830401Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:36.830402Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-18T11:08:36.846260Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:08:36.846267Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:37.200322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:37.204550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:44.569422Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:08:44.580109Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:44.662911Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:08:44.662911Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs": [ ] +2024-07-18T11:08:44.963152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:44.963186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:08:48.598218Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:09:02.419903Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:09:02.839084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:04.026138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:09:04.187817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:04.686296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:16.981168Z | Info | Live bytes: 789.14MB Heap size: 2663.38MB +2024-07-18T11:09:32.222594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:32.826312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:33.656417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:34.520089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:35.230333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:35.833419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:48.912609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:49.540991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:50.074282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:09:55.652776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:10:04.619701Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:10:16.993943Z | Info | Live bytes: 819.08MB Heap size: 2663.38MB +2024-07-18T11:11:16.996183Z | Info | Live bytes: 823.81MB Heap size: 2663.38MB +2024-07-18T11:11:27.615958Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:11:31.094718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:13.156871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:17.001497Z | Info | Live bytes: 849.11MB Heap size: 2663.38MB +2024-07-18T11:12:39.246359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:42.506983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:43.102645Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:43.985342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:44.825734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:46.748003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:49.602714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:51.575022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:52.606043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:53.855896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:56.068730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:56.575249Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:57.086881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:57.670777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:12:58.271444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:13:17.016138Z | Info | Live bytes: 971.00MB Heap size: 2663.38MB +2024-07-18T11:13:23.538647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:13:23.751822Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:13:24.406523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:13:30.592998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:13:31.700274Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:14:00.830900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:14:17.031895Z | Info | Live bytes: 1013.33MB Heap size: 2663.38MB +2024-07-18T11:15:13.746823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:15:16.265670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:15:17.034028Z | Info | Live bytes: 1007.48MB Heap size: 2663.38MB +2024-07-18T11:16:17.094363Z | Info | Live bytes: 1007.48MB Heap size: 2663.38MB +2024-07-18T11:17:17.128298Z | Info | Live bytes: 1007.48MB Heap size: 2663.38MB +2024-07-18T11:18:17.156160Z | Info | Live bytes: 1007.48MB Heap size: 2663.38MB +2024-07-18T11:18:59.076284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:18:59.969764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:00.345059Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:00.528472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:00.726462Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:00.788864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:00.909884Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:00.971995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:01.056770Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:01.170159Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:01.370096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:01.435050Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:01.666646Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:01.745255Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:01.897359Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:02.468883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:03.139756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:03.665100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:04.652063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:05.505399Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:05.866689Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:06.235893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:06.911819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:07.478728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:08.642517Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:08.732890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:08.855342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:08.902953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:09.809369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:10.530768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:10.654642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:11.070548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:11.118731Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:11.305847Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:11.773225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:11.808313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:11.964334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:12.272216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:12.922134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:13.000690Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:13.140115Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:13.314713Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:13.467788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:14.040342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:15.024583Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:15.913942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:16.461262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:17.158368Z | Info | Live bytes: 1049.03MB Heap size: 2663.38MB +2024-07-18T11:19:19.112316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:29.151978Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:29.626100Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:29.995040Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:30.044494Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:19:30.488526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:31.120483Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:32.324409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:32.838092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:33.621301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:35.691197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:36.221477Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:19:36.794708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:19:39.040388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:17.199191Z | Info | Live bytes: 1070.79MB Heap size: 2663.38MB +2024-07-18T11:20:22.829450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:23.730284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:31.878700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:41.840629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:43.494803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:48.762765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:51.278257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:51.366584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:20:51.814611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:53.849151Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:20:54.296801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:54.857434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:20:55.255109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:20:55.706137Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:11.232407Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:11.270734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:11.382451Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:11.468714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:11.523144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:11.579627Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:11.857002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:11.892315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:12.005672Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:12.111947Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:12.276283Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:12.441921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:12.468223Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:12.666326Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:12.788111Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:12.870813Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:13.004036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:13.129534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:13.814191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:13.855821Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:14.312914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:14.537859Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:21:17.200653Z | Info | Live bytes: 1217.17MB Heap size: 2663.38MB +2024-07-18T11:21:20.073786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:31.965722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:46.631978Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:50.820041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:51.827405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:52.457432Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:21:52.459423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:53.255466Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:54.560096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:55.821532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:21:56.375247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:00.737075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:01.399372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:02.018134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:02.032143Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:22:02.868796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:17.210229Z | Info | Live bytes: 1273.26MB Heap size: 2663.38MB +2024-07-18T11:22:19.087453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:20.168009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:20.878007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:38.684913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:39.751302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:22:39.847980Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:22:39.950561Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:22:40.101873Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:22:40.214770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:40.246330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:22:40.724496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:41.066804Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:22:41.723355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:50.344673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:50.854863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:50.895981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:22:52.123878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:53.072730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:53.569443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:56.220667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:22:58.157755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:00.357614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:04.441229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:04.671941Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:05.029532Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:05.112653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:05.345735Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:05.695392Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:17.217605Z | Info | Live bytes: 813.55MB Heap size: 2971.66MB +2024-07-18T11:23:18.703863Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:19.960643Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:20.032075Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:20.116273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:20.202059Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:20.425997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:20.462675Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:20.944529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:21.846037Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:23:21.907962Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-18T11:23:21.986114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:31.380185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:31.906412Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:31.979446Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:23:32.424486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:38.097493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:55.163876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:57.078074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:57.613622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:23:58.506777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:17.227906Z | Info | Live bytes: 1057.16MB Heap size: 2971.66MB +2024-07-18T11:24:18.019937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:18.840675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:19.445173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:19.571887Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:24:20.033287Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:20.716335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:21.354187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:21.955538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:22.965737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:23.751661Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:24.496726Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:25.266394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:24:25.461696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:26.025487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:29.795741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:24:30.212722Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:31.026991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:24:31.087377Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:24:31.421294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:24:43.456923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:01.499910Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:02.849488Z | Info | LSP: received shutdown +2024-07-18T11:25:02.851558Z | Error | Got EOF +2024-07-18T11:25:15.114197Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-18T11:25:15.115294Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-18T11:25:15.115637Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T11:25:15.118900Z | Info | Logging heap statistics every 60.00s +2024-07-18T11:25:15.125446Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-18T11:25:15.125828Z | Info | Starting server +2024-07-18T11:25:15.127259Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-18T11:25:15.195576Z | Info | Started LSP server in 0.07s +2024-07-18T11:25:16.412631Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Eras/Core.hs +2024-07-18T11:25:16.413214Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-18T11:25:16.926036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:16.926041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:17.914280Z | Info | Load cabal cradle using single file +2024-07-18T11:25:18.811839Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT127419-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-18T11:25:25.870518Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-18T11:25:25.877871Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-18T11:25:39.885948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:44.054147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:44.549110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:45.049781Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:45.544858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:47.729385Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:47.867967Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:25:48.524774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:25:51.876662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:26:12.485311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:26:15.122863Z | Info | Live bytes: 765.01MB Heap size: 1973.42MB +2024-07-18T11:26:18.702670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:26:20.086092Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:26:38.545505Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:26:38.733042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:26:38.786474Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:26:39.162891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:26:39.849153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:26:40.515291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:26:40.651405Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:26:52.633368Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:26:53.060357Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:00.195410Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:27:15.136692Z | Info | Live bytes: 517.61MB Heap size: 2358.25MB +2024-07-18T11:27:32.781662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:32.901559Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:27:33.355652Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:34.479983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:37.733248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:38.245403Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:44.963057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:45.263736Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:27:45.919214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:48.705840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:53.621329Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:58.386404Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:27:58.762788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:27:59.621908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:00.180198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:04.063570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:04.652924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:05.445354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:05.982861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:15.142141Z | Info | Live bytes: 810.00MB Heap size: 2358.25MB +2024-07-18T11:28:49.722062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:50.193931Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:28:50.316895Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:28:50.800836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:54.826493Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:28:54.899056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:28:55.059641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:56.274586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:57.815166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:58.793176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:28:59.574826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:00.618138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:00.696775Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:00.843853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:01.517213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:01.690583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:01.975805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:02.099651Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:02.204694Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:02.553239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:02.847442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:02.924647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:03.043092Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:03.134222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:03.532780Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:03.579396Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:03.698944Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:03.984994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:04.739973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:05.036458Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:05.382154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:06.553713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:14.576026Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:29:15.143676Z | Info | Live bytes: 947.37MB Heap size: 2358.25MB +2024-07-18T11:29:30.442151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:31.367704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:33.866879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:35.330740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:36.387548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:29:36.418328Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:29:56.426902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:30:00.863003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:30:15.154287Z | Info | Live bytes: 951.89MB Heap size: 2358.25MB +2024-07-18T11:31:15.214817Z | Info | Live bytes: 951.89MB Heap size: 2358.25MB +2024-07-18T11:31:26.747977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:31:30.829104Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:31:30.978679Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:31:31.247556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:31:32.157326Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:31:32.216790Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:31:32.295503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:31:32.596868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:31:32.994274Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:31:43.236568Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:31:43.837377Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:31:50.246439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:31:50.563293Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:31:50.737455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:31:55.823700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:00.272372Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:01.174698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:14.317536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:15.217278Z | Info | Live bytes: 981.47MB Heap size: 2358.25MB +2024-07-18T11:32:15.637782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:18.471969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:23.493038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:24.734635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:27.105881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:27.786626Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:32:28.342920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:43.020587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:52.967268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:32:53.261591Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:33:15.236341Z | Info | Live bytes: 616.73MB Heap size: 2610.95MB +2024-07-18T11:33:54.173331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:33:54.644217Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T11:33:59.639571Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:33:59.840786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:34:15.248447Z | Info | Live bytes: 871.76MB Heap size: 2610.95MB +2024-07-18T11:35:11.124193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:14.889076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:15.250127Z | Info | Live bytes: 898.63MB Heap size: 2610.95MB +2024-07-18T11:35:15.758546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:16.135360Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:35:16.787705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:19.702471Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:21.919335Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:22.610805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:23.444789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:35:23.946912Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:36:15.278789Z | Info | Live bytes: 908.06MB Heap size: 2610.95MB +2024-07-18T11:37:15.339352Z | Info | Live bytes: 908.06MB Heap size: 2610.95MB +2024-07-18T11:38:15.369803Z | Info | Live bytes: 908.06MB Heap size: 2610.95MB +2024-07-18T11:38:21.967022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:38:22.394233Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:22.885975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:23.489963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:24.561962Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:26.235663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:28.645816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:38:28.880061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:29.373968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:32.869182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:33.706270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:33.815705Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:38:34.267023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:34.780864Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:35.580487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:37.862801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:38.346862Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:38:38.953062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:40.325943Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:40.392289Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:38:52.147511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:53.404508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:56.668880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:57.246061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:38:58.219534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:07.269698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:11.328692Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:39:11.435715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:39:11.739602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:12.318229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:13.549829Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:15.372388Z | Info | Live bytes: 1025.58MB Heap size: 2610.95MB +2024-07-18T11:39:16.835429Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:18.747491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:22.549900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:25.482832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:25.996045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:26.498698Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:27.263794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:29.524437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:48.354927Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:48.872056Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:51.601101Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:58.697438Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:39:59.427080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:00.005787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:02.817998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:04.925814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:06.145785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:06.824753Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:07.522434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:10.830966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:14.566636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:40:14.747442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:40:14.970988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:15.373242Z | Info | Live bytes: 546.34MB Heap size: 2650.80MB +2024-07-18T11:40:17.047935Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:40:17.347855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:25.081897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:25.744754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:27.225534Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:28.165699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:28.683492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:40.323314Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:40:40.869738Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:49.449515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:49.548873Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T11:40:53.267239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:54.810752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:55.471488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:57.130344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:57.550529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:40:57.691694Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:40:58.376656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:41:03.318106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:41:03.823550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:41:04.249495Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:41:12.955789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:41:15.376707Z | Info | Live bytes: 651.42MB Heap size: 2650.80MB +2024-07-18T11:41:18.601136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:41:18.852293Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:42:03.589169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:08.786798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:09.430315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:10.845552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:10.962425Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:42:15.381649Z | Info | Live bytes: 669.90MB Heap size: 2650.80MB +2024-07-18T11:42:31.780196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:31.999589Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:42:44.865202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:47.589305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:49.005389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:42:49.437418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:42:49.646197Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:42:55.182311Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:42:55.341173Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:15.401967Z | Info | Live bytes: 685.15MB Heap size: 2650.80MB +2024-07-18T11:43:20.728022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:21.303947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:21.799547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:22.310275Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:22.838153Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:23.161055Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T11:43:35.560531Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:43:35.665587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:43:35.948036Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:37.203860Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:43:45.617659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:48.274881Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:48.827826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:49.063246Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T11:43:57.778242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:43:59.578211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:44:02.428918Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:44:05.797515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:44:06.137985Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T11:44:15.407156Z | Info | Live bytes: 865.03MB Heap size: 2650.80MB +2024-07-18T11:45:15.467603Z | Info | Live bytes: 865.03MB Heap size: 2650.80MB +2024-07-18T11:46:15.481572Z | Info | Live bytes: 865.03MB Heap size: 2650.80MB +2024-07-18T11:47:08.198937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:47:15.487579Z | Info | Live bytes: 858.60MB Heap size: 2650.80MB +2024-07-18T11:47:31.307202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:47:36.068176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:47:43.979175Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-18T11:47:43.979695Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-18T11:47:44.078746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:47:45.728805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:47:49.722892Z | Info | Load cabal cradle using single file +2024-07-18T11:47:50.790939Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT127419-86 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-18T11:48:15.516425Z | Info | Live bytes: 874.50MB Heap size: 2650.80MB +2024-07-18T11:48:25.746949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:48:26.523798Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:48:43.423808Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-af8441dbb3602f7131921f13c15272adfaab98f9 +2024-07-18T11:48:43.423988Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-af8441dbb3602f7131921f13c15272adfaab98f9 +2024-07-18T11:48:43.428507Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.0.0.0-inplace + , cardano-api-9.0.0.0-inplace-internal ] +2024-07-18T11:49:15.543006Z | Info | Live bytes: 1135.11MB Heap size: 2915.04MB +2024-07-18T11:49:29.302640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:30.404128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:31.054390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:31.624907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:32.166774Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:32.752634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:33.330348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:33.866154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:34.399593Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:35.092025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:35.587620Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:36.158284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:36.876336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:37.421447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:37.928183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:38.498156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:38.992755Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:39.525312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:40.079663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:41.107478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:41.722798Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:42.313639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:42.838225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:43.424831Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:44.255271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:44.827913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:45.494229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:46.101996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:46.651032Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:47.173800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:47.709538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:48.267727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:48.918801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:49.459765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:50.178735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:51.052811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:51.591157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:52.675133Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:53.192174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:54.442706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:55.034535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:58.970044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:49:59.544639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:00.823573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:02.315445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:03.506874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:04.120594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:05.556050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:06.125364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:06.935363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:07.524743Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:08.346874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:08.860459Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:09.374656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:09.884462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:10.402323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:10.975697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:11.242240Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:50:11.901050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:15.547941Z | Info | Live bytes: 1492.30MB Heap size: 3150.97MB +2024-07-18T11:50:48.889342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:49.446218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:50.018307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:50:50.105206Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:50:50.457902Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:51.305186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:51.932631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:52.543387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:50:52.589508Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:50:52.642648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:50:52.669109Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T11:50:59.675574Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T11:51:15.564158Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:52:15.613770Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:52:36.826113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T11:53:15.616678Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:54:15.621059Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:55:15.624030Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:56:15.682685Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:57:15.713601Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:58:15.724807Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T11:59:15.751632Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T12:35:54.523290Z | Info | Live bytes: 1543.69MB Heap size: 3150.97MB +2024-07-18T12:36:32.266900Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:36:33.656895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:36:34.433447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:36:35.035276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:36:35.623587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:36:36.141160Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:36:54.541976Z | Info | Live bytes: 1573.05MB Heap size: 3156.21MB +2024-07-18T12:36:55.799819Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:37:52.599348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:37:54.589326Z | Info | Live bytes: 1047.55MB Heap size: 3532.65MB +2024-07-18T12:38:08.704777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:38:22.137259Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:38:23.576690Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:38:23.602793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:38:54.596484Z | Info | Live bytes: 1047.55MB Heap size: 3532.65MB +2024-07-18T12:39:33.461515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:33.940202Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:34.077211Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:34.149584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:34.338504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:35.596097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:37.168742Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:37.679860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:38.443809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:39.306405Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:39.362170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:39.549052Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:39.718265Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:39.866426Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:39.985899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:40.005394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:40.279983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:40.701047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:41.105852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:41.540312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:44.165972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:44.678455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:46.647657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:49.353284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:49.974696Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:50.089370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:50.186946Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:50.580342Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:39:51.033400Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:51.969105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:52.835710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:53.662578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:54.199570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:54.597284Z | Info | Live bytes: 1157.07MB Heap size: 3532.65MB +2024-07-18T12:39:55.195542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:55.701433Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:56.507657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:57.468663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:58.019619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:58.719695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:39:59.743457Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:00.274611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:00.787907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:01.323189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:09.300116Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:09.837135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:16.185516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:16.716636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:39.274850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:40:54.600837Z | Info | Live bytes: 1649.67MB Heap size: 3532.65MB +2024-07-18T12:41:11.106430Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:41:18.534674Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:41:24.431555Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:41:54.603147Z | Info | Live bytes: 1761.08MB Heap size: 3532.65MB +2024-07-18T12:42:54.663569Z | Info | Live bytes: 1761.08MB Heap size: 3532.65MB +2024-07-18T12:43:07.968007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:09.153112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:09.766033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:10.386952Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:11.775582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:12.374351Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:13.316047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:13.829044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:15.617125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:16.367083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:26.590957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:28.710175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:29.549131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:31.780519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:35.483247Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:43:54.675459Z | Info | Live bytes: 1794.80MB Heap size: 3532.65MB +2024-07-18T12:44:54.736039Z | Info | Live bytes: 1794.80MB Heap size: 3532.65MB +2024-07-18T12:45:33.810350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:45:54.757824Z | Info | Live bytes: 1794.80MB Heap size: 3532.65MB +2024-07-18T12:46:06.202276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:07.100559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:14.401757Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:16.754143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:17.529788Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:23.682800Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:24.813855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:54.788350Z | Info | Live bytes: 1811.50MB Heap size: 3532.65MB +2024-07-18T12:46:55.814304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:57.256196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:46:57.343825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:46:57.726939Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:46:58.222020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:47:36.562369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:47:37.092551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:47:47.956188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:47:54.796836Z | Info | Live bytes: 1827.24MB Heap size: 3532.65MB +2024-07-18T12:48:19.738600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:48:20.507738Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-18T12:48:49.679662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:48:54.797562Z | Info | Live bytes: 1901.33MB Heap size: 3532.65MB +2024-07-18T12:49:54.857998Z | Info | Live bytes: 1901.33MB Heap size: 3532.65MB +2024-07-18T12:50:54.918377Z | Info | Live bytes: 1901.33MB Heap size: 3532.65MB +2024-07-18T12:50:55.437170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:50:58.660991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:50:59.558964Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T12:51:05.045873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:06.288623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:07.718635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:08.373008Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:08.903155Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T12:51:15.735134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:16.306504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:17.629836Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T12:51:27.546480Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:51:27.712351Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:51:27.819565Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:51:27.836147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:28.653514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:51:29.110741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:29.632603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:35.469154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:35.657793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:51:36.000265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:43.468186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:44.180719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:44.927232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:45.682237Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:46.124569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:51:46.585536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:47.086200Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:47.682390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:48.323983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:48.902337Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:50.401181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:50.511265Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T12:51:54.224971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:51:54.922999Z | Info | Live bytes: 1958.91MB Heap size: 3532.65MB +2024-07-18T12:52:04.605126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:52:04.985077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:52:05.093273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:52:05.107832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:52:06.524287Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:52:16.242977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:52:34.905477Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:52:35.863027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:52:40.023941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:52:49.066953Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:52:54.929455Z | Info | Live bytes: 1991.97MB Heap size: 3532.65MB +2024-07-18T12:52:59.975422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:01.562138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:04.863076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:09.310146Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:09.454624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:09.747601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:09.869031Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:10.108954Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:10.180909Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:10.350257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:10.424783Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:10.538773Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:10.906263Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:10.954037Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:11.087548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:11.157712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:11.430230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:23.255325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:23.406246Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:23.553356Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:23.699987Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:24.215925Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:24.891055Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:27.427195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:42.648566Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:53:43.114951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:43.136048Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:53:54.645063Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:53:54.930856Z | Info | Live bytes: 2069.98MB Heap size: 3532.65MB +2024-07-18T12:53:55.168197Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:54:45.531494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:54:46.261823Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:54:46.422258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:54:54.940315Z | Info | Live bytes: 1173.60MB Heap size: 4020.24MB +2024-07-18T12:55:54.973491Z | Info | Live bytes: 1173.60MB Heap size: 4020.24MB +2024-07-18T12:56:22.925085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:56:29.138517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:56:55.006353Z | Info | Live bytes: 1173.60MB Heap size: 4020.24MB +2024-07-18T12:57:54.604202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:57:55.008260Z | Info | Live bytes: 1154.49MB Heap size: 4020.24MB +2024-07-18T12:57:58.935404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:01.414317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:58:01.475387Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:58:01.631394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:58:01.699880Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:58:01.831779Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:58:01.874959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:02.202831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:58:02.685344Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:03.178850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:03.723658Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:58:04.329059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:20.290985Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:58:20.750501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:24.426686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:42.291080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:42.801034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:49.583545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:50.076591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:51.767638Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T12:58:55.010711Z | Info | Live bytes: 1567.69MB Heap size: 4020.24MB +2024-07-18T12:58:56.028177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:58:57.491930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:01.330274Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:02.249737Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:02.665229Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T12:59:05.277142Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:59:11.634076Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:59:11.684994Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:59:11.829618Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:59:11.874796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:11.907908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:59:11.933434Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T12:59:12.386708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:12.832228Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:59:13.487554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:22.902607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:23.542572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:24.052470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:24.562841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:25.979763Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T12:59:27.013795Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T12:59:55.035535Z | Info | Live bytes: 1165.24MB Heap size: 4057.99MB +2024-07-18T13:00:15.960238Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:00:16.484192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:00:21.830714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:00:29.623379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:00:29.676009Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:00:29.828733Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:00:29.831439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:00:29.901802Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:00:29.971953Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:00:30.379192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:00:30.638988Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:00:31.296002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:00:55.055468Z | Info | Live bytes: 1285.42MB Heap size: 4057.99MB +2024-07-18T13:01:55.115432Z | Info | Live bytes: 1285.42MB Heap size: 4057.99MB +2024-07-18T13:02:22.366240Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:22.426769Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:22.561272Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:22.590836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:02:22.635719Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:22.706053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:23.065597Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:23.106458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:02:23.182292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:23.279490Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:23.338403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:23.485778Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:23.653290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:02:24.071308Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:24.262252Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:24.369920Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:24.544141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:02:25.443482Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:02:25.908747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:02:26.223469Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:02:26.888580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:02:55.138515Z | Info | Live bytes: 1447.30MB Heap size: 4057.99MB +2024-07-18T13:03:55.194311Z | Info | Live bytes: 1447.30MB Heap size: 4057.99MB +2024-07-18T13:04:55.195462Z | Info | Live bytes: 1447.30MB Heap size: 4057.99MB +2024-07-18T13:05:47.622126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:05:47.968335Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:48.119430Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:48.172193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:48.249991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:48.436002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:05:49.414053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:05:50.929083Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:05:53.058151Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:53.213507Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:53.254601Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:53.339254Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:05:53.522882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:05:55.197431Z | Info | Live bytes: 1468.69MB Heap size: 4057.99MB +2024-07-18T13:06:02.151272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:06:02.713093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:06:04.051091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:06:11.486716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:06:11.559734Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:06:11.658966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:06:11.943405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:06:55.236159Z | Info | Live bytes: 1495.99MB Heap size: 4057.99MB +2024-07-18T13:07:35.372653Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:39.697745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:41.848600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:42.522256Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:42.791268Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:42.970140Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:42.994152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:43.493657Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:43.776542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:43.912703Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:43.956306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:43.976362Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:44.105415Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:44.195763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:44.289580Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:07:44.452453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:45.053975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:47.290417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:07:47.601160Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:07:55.244421Z | Info | Live bytes: 1504.65MB Heap size: 4057.99MB +2024-07-18T13:08:07.829197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:12.787320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:16.447368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:17.135259Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:08:24.974076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:26.776428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:29.359311Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:31.231862Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:34.807906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:36.313492Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:37.123766Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:08:55.257546Z | Info | Live bytes: 1823.43MB Heap size: 4057.99MB +2024-07-18T13:09:55.317490Z | Info | Live bytes: 1823.43MB Heap size: 4057.99MB +2024-07-18T13:10:55.352564Z | Info | Live bytes: 1823.43MB Heap size: 4057.99MB +2024-07-18T13:11:07.040158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:07.651637Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:07.719173Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:07.914599Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:07.999995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:08.071156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:09.617606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:12.558295Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:16.373849Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:18.082639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:18.157199Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:18.223841Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:18.391659Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:18.591875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:19.679144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:20.224154Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:20.306178Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:20.467973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:20.658054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:21.194777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:21.941966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:29.756230Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:11:37.533749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:37.614315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:37.768361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:37.844305Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:37.966426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:38.525517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:43.350069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:47.895291Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:11:48.290923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:11:48.512304Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:11:55.359457Z | Info | Live bytes: 1899.57MB Heap size: 4057.99MB +2024-07-18T13:12:55.419400Z | Info | Live bytes: 1899.57MB Heap size: 4057.99MB +2024-07-18T13:13:55.479490Z | Info | Live bytes: 1899.57MB Heap size: 4057.99MB +2024-07-18T13:14:55.539553Z | Info | Live bytes: 1899.57MB Heap size: 4057.99MB +2024-07-18T13:15:55.599725Z | Info | Live bytes: 1899.57MB Heap size: 4057.99MB +2024-07-18T13:16:55.659564Z | Info | Live bytes: 1899.57MB Heap size: 4057.99MB +2024-07-18T13:17:45.794177Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:46.001467Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:46.212973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:46.312402Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:46.766592Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:46.968023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:47.064419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:47.416652Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:51.554879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:51.599121Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:51.774288Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:51.789045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:51.863369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:51.940772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:51.979811Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:52.298325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:52.316704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:52.398193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:52.518518Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:52.587447Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:52.709579Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:52.848799Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:53.208000Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:53.368252Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:53.447350Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:53.505658Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:17:53.644285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:54.070142Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:17:54.700981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:17:55.660427Z | Info | Live bytes: 1949.04MB Heap size: 4057.99MB +2024-07-18T13:18:08.270159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:08.911051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:09.038796Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:09.075434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:09.133837Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:09.570188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:10.482158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:11.721840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:12.278322Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:14.345573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:14.442094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:14.553044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:15.097061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:15.646317Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:15.738194Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:16.365911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:16.937258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:17.695138Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:17.849728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:17.987310Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:18.271093Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:18.283641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:18.795554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:19.637877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:19.709942Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:18:20.333650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:25.276853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:26.515735Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:26.609997Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:26.776394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:26.944306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:26.946725Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:27.758380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:30.781860Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:18:31.407086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:43.512810Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:43.599610Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:43.724576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:43.782683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:43.807586Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:43.824024Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:44.195124Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:44.275188Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:44.300274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:44.391900Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:44.772525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:45.203311Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:45.535381Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:45.854530Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:46.150949Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:46.310959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:46.332226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:46.385792Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:46.454112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:18:46.837369Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:18:46.850956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:47.513031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:18:55.662464Z | Info | Live bytes: 1284.22MB Heap size: 4145.02MB +2024-07-18T13:19:07.886064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:19:08.422353Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-18T13:19:55.709906Z | Info | Live bytes: 1311.47MB Heap size: 4145.02MB +2024-07-18T13:20:55.769508Z | Info | Live bytes: 1311.47MB Heap size: 4145.02MB +2024-07-18T13:21:24.591513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:21:25.695196Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:21:28.454811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:21:30.527155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:21:55.791273Z | Info | Live bytes: 1301.25MB Heap size: 4145.02MB +2024-07-18T13:22:55.851594Z | Info | Live bytes: 1301.25MB Heap size: 4145.02MB +2024-07-18T13:23:55.888448Z | Info | Live bytes: 1301.25MB Heap size: 4145.02MB +2024-07-18T13:24:55.899474Z | Info | Live bytes: 1301.25MB Heap size: 4145.02MB +2024-07-18T13:25:04.708012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:05.462166Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:05.528298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:05.644315Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:05.739624Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:05.819084Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:05.892374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:05.950908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:06.021056Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:06.119715Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:06.392559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:06.608621Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:06.686138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:06.763906Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:06.958222Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:07.059665Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:07.659382Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:08.807515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:09.441689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:09.452937Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:09.499269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:09.867110Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:09.952648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:12.135281Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:12.147128Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:12.680750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:13.661113Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:13.828638Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:14.264614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:14.800713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:17.094183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:17.737608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:18.608701Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:20.765042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:21.309046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:21.626546Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:21.834019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:22.408730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:23.368037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:24.274542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:25:24.714761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:25.374354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:26.154125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:26.779439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:27.354157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:48.983521Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:52.154563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:52.792686Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:25:55.903485Z | Info | Live bytes: 1361.59MB Heap size: 4145.02MB +2024-07-18T13:26:22.787224Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:23.524024Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:24.188624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:24.723627Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:25.973713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:28.161491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:29.616404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:30.660951Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:31.340224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:31.777571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:32.871775Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:33.418082Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:34.387465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:34.984707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:35.468105Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:35.573745Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:35.597095Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:36.470551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:37.003093Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:37.586787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:38.035527Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:38.160406Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:38.396980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:38.835232Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:39.287648Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:40.298097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:40.638357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:41.083255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:41.609982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:42.067189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:43.597230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:44.401624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:46.491964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:47.221971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:47.905533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:48.304844Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:48.539257Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:49.432599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:49.996427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:50.594241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:51.549548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:52.067737Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:52.108110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:52.157339Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:26:52.603231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:55.340062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:26:55.904620Z | Info | Live bytes: 1385.77MB Heap size: 4145.02MB +2024-07-18T13:27:00.064449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:01.465307Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:01.570094Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:01.638983Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:01.704019Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:01.760375Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:01.762178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:02.511829Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:27:02.578326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:03.136633Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:09.096777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:10.163984Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:10.569109Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:11.330258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:11.758956Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:12.695778Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:27:13.099384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:27:55.945497Z | Info | Live bytes: 1632.13MB Heap size: 4145.02MB +2024-07-18T13:28:20.635201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:21.509033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:23.914432Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:25.123051Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:28:25.130348Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:25.786712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:34.436886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:39.429059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:43.225572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:28:43.364554Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:28:43.488607Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:28:43.652295Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:28:43.690609Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:44.309169Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:28:44.464452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:28:55.950968Z | Info | Live bytes: 1964.67MB Heap size: 4145.02MB +2024-07-18T13:28:58.890144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:07.371199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:11.579307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:14.576001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:16.208873Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:19.083614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:20.989198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:21.023098Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:34.290320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:34.551105Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:29:41.071810Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:29:41.247929Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:29:41.452839Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:29:41.481641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:42.116105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:45.206727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:51.990183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:52.495878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:55.955412Z | Info | Live bytes: 2054.40MB Heap size: 4145.02MB +2024-07-18T13:29:57.053632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:29:58.235893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:30:05.460114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:30:05.954493Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:30:06.104865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:30:06.760073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:30:07.503721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:30:55.997872Z | Info | Live bytes: 1123.83MB Heap size: 4145.02MB +2024-07-18T13:31:43.721097Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:31:43.832628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:31:44.049048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:31:44.169877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:31:44.674519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:31:56.005533Z | Info | Live bytes: 1139.64MB Heap size: 4145.02MB +2024-07-18T13:32:06.856029Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:19.377253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:19.713260Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:32:19.943072Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:32:20.109840Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:32:20.161195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:20.403889Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:32:20.714635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:21.747028Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:23.294771Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:32:23.379805Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:32:23.514445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:23.572747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:32:24.032325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:35.116990Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:35.718740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:32:56.021609Z | Info | Live bytes: 1157.16MB Heap size: 4145.02MB +2024-07-18T13:33:08.421563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:08.591940Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:08.679503Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:08.789168Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:08.867069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:09.361700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:10.572883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:11.346837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:12.316279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:19.078274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.150868Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.306929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:19.318401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.378921Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.448062Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.509164Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.781519Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.833053Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:19.927417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:19.977963Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:20.055001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:20.385551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:20.397844Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:20.412642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:20.712205Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:20.900825Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:20.990174Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:21.169066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:21.241401Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:21.402245Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:21.581239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:21.701289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:21.782308Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:21.893345Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:21.949591Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:22.127419Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:22.237289Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:22.237484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:40.647863Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:40.799996Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:40.817320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:40.843846Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:41.005858Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:41.238379Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:41.461388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:41.600673Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:41.761190Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:41.841909Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:41.920702Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:42.004279Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:33:42.062213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:42.505814Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:33:43.164740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:33:56.030912Z | Info | Live bytes: 1492.84MB Heap size: 4145.02MB +2024-07-18T13:34:05.037360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:05.710810Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:05.883642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:05.989593Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:06.085475Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:06.157875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:07.180190Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:07.280777Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:07.417651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:08.358092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:08.840720Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:09.030010Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:09.111908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:09.187191Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:09.282877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:09.966886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:10.602476Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:11.467814Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:11.993491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:12.031051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:12.493945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:13.259418Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:14.000989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:14.731183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:15.344445Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:15.400764Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:15.510377Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:15.575469Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:15.617104Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:15.696540Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:15.790030Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:15.840088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:15.847365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:16.423552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:20.104110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:22.567513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:23.784765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:25.186523Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:27.003538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:30.518070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:32.353673Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:32.454927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:32.501739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:32.590001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:32.690790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:32.699248Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:32.778464Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:33.235163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:34.101507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:34.629314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:35.124805Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:35.178302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:35.246881Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:35.268089Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:35.671053Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:36.130794Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:36.236536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:36.335611Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:36.422816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:36.509757Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:36.694893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:37.113638Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:37.191758Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:37.247268Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:37.346817Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:37.443636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:37.894441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:38.562539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:38.616239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:39.077706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:39.258578Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:39.362169Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:39.653999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:40.212929Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:40.773103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:41.427067Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:41.677510Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:41.782498Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:34:41.984599Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:42.495890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:43.595245Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:44.174710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:44.674189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:45.312584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:46.108378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:46.690104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:47.440526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:48.386937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:49.183605Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:54.357582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:55.657615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:34:56.032066Z | Info | Live bytes: 1603.76MB Heap size: 4145.02MB +2024-07-18T13:35:00.359343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:04.102796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:04.999323Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:06.955229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:07.533573Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:08.479718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:09.012769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:09.290991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:35:09.626670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:15.827306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:18.828896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:19.627099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:21.642680Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:25.033273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:35:25.450564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:28.250995Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:35:28.258189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:28.346934Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:35:28.798340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:30.806896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:31.338972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:31.990448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:32.889106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:33.217511Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:35:33.663205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:34.926888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:35.348563Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:35:36.001597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:35:56.052583Z | Info | Live bytes: 1623.09MB Heap size: 4145.02MB +2024-07-18T13:36:25.265986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:25.428035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-18T13:36:25.886454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:39.693314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:41.009243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:41.579250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:42.499498Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:43.485316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:44.654013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:45.914758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:48.427765Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:36:56.055793Z | Info | Live bytes: 1636.03MB Heap size: 4145.02MB +2024-07-18T13:37:56.056808Z | Info | Live bytes: 1636.03MB Heap size: 4145.02MB +2024-07-18T13:38:56.117481Z | Info | Live bytes: 1636.03MB Heap size: 4145.02MB +2024-07-18T13:39:56.132110Z | Info | Live bytes: 1636.03MB Heap size: 4145.02MB +2024-07-18T13:40:56.192657Z | Info | Live bytes: 1636.03MB Heap size: 4145.02MB +2024-07-18T13:41:48.645852Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:49.177546Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:49.684663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:50.347566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:50.910823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:51.411442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:51.950157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:52.457314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:53.003453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:53.597084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:54.123903Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:54.645378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:55.156784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:55.677228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:56.193242Z | Info | Live bytes: 1667.29MB Heap size: 4145.02MB +2024-07-18T13:41:56.397012Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:56.965309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:57.581315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:58.156547Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:58.696488Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:59.204103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-18T13:41:59.535732Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-18T13:42:56.198179Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:43:56.258669Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:44:56.319222Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:45:56.365613Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:46:56.426276Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:47:56.429643Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:48:56.461715Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:49:56.493541Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:50:56.525704Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:51:56.553683Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:52:56.577175Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:53:56.621582Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:54:56.678544Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:55:56.739194Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:56:56.799724Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:57:56.849582Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:58:56.905597Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T13:59:56.927861Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:00:56.988207Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:01:57.048577Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:02:57.108514Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:03:57.146967Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:04:57.185135Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:05:57.222522Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:06:57.283093Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:07:57.343755Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:08:57.404137Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:09:57.445598Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:10:57.505998Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:11:57.553700Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:12:57.583678Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:13:57.584550Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:14:57.644916Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:15:57.693589Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:16:57.753828Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:17:57.814363Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:18:57.874930Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:19:57.935477Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:20:57.996108Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:21:58.005606Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:22:58.041939Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:23:58.101588Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:24:58.161383Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:25:58.181596Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:26:58.229588Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:27:58.285690Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:28:58.346419Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:29:58.349672Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:30:58.389155Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:31:58.449824Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:32:58.510429Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:33:58.556868Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:34:58.586112Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:35:58.646842Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:36:58.648155Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:37:58.708755Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:38:58.715596Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:39:58.720564Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:40:58.765636Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:41:58.826246Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:42:58.886971Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:43:58.947662Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:44:58.957708Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:45:59.018410Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:46:59.079028Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:47:59.089335Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:48:59.093725Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:49:59.117686Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:50:59.178320Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:51:59.239054Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:52:59.299717Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:53:59.359750Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:54:59.420513Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:55:59.458466Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:56:59.497365Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:57:59.555496Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:58:59.615874Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T14:59:59.671027Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:00:59.731736Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:01:59.738679Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:02:59.798510Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:03:59.827996Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:04:59.853647Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:05:59.861664Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:06:59.862322Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:07:59.922968Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:08:59.983615Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:10:00.037850Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:11:00.098481Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:12:00.159195Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:13:00.219886Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:14:00.280552Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:15:00.341247Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:16:00.401872Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:17:00.445439Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:18:00.506098Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:19:00.566675Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:20:00.627247Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:21:00.635504Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:22:00.696172Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:23:00.756766Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:24:00.817341Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:25:00.877758Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:26:00.914651Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:27:00.975169Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:28:00.979612Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:29:01.005729Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:30:01.066364Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:31:01.125508Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:32:01.183373Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:33:01.197700Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:34:01.216040Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:35:01.276618Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:36:01.293673Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:37:01.332480Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:38:01.357564Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:39:01.418089Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:40:01.478581Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:41:01.539060Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:42:01.581637Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:43:01.623259Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:44:01.683887Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:45:01.704878Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:46:01.757676Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:47:01.818238Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:48:01.820943Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:49:01.881636Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:50:01.942091Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:51:02.002736Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:52:02.063347Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:53:02.114538Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:54:02.175064Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:55:02.235615Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:56:02.296169Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:57:02.356761Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:58:02.417304Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T15:59:02.477923Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:00:02.538499Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:01:02.599070Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:02:02.637672Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:03:02.698288Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:04:02.759081Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:05:02.797612Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:06:02.858240Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:07:02.901674Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:08:02.962300Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:09:03.023052Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:10:03.083745Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:11:03.144369Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:12:03.205067Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:13:03.245660Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:14:03.306294Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:15:03.366963Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:16:03.372699Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:17:03.421078Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:18:03.481608Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:19:03.510365Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:20:03.557618Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:21:03.565704Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:22:03.619716Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:23:03.674020Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:24:03.725664Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:25:03.757618Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:26:03.818158Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:27:03.869672Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:28:03.917668Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:29:03.969208Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:30:03.981695Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:31:03.996243Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:32:04.010046Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:33:04.069654Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:34:04.109702Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:35:04.170212Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:36:04.230738Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:37:04.291198Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:38:04.351907Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:39:04.373662Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:40:04.434391Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:41:04.495006Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:42:04.555712Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:43:04.616488Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:44:04.677269Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:45:04.738110Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:46:04.798932Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:47:04.859713Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:48:04.920452Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:49:04.981210Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:50:05.041889Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:51:05.101631Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:52:05.161394Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:53:05.165679Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:54:05.225639Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:55:05.286362Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:56:05.347105Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:57:05.407839Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:58:05.468624Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T16:59:05.529401Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:00:05.590249Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:01:05.651103Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:02:05.711937Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:03:05.771579Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:04:05.820884Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:05:05.881608Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:06:05.942305Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:07:06.003039Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:08:06.063782Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:09:06.124488Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:10:06.185177Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:11:06.245865Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:12:06.306604Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:13:06.367240Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:14:06.427941Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:15:06.488514Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:16:06.540650Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:17:06.601416Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:18:06.605672Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:19:06.666400Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:20:06.727145Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:21:06.787851Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:22:06.848588Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:23:06.909303Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:24:06.970007Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:25:07.028306Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:26:07.088730Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:27:07.097584Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:28:07.158218Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:29:07.218957Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:30:07.279660Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:31:07.340356Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:32:07.400966Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:33:07.461586Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:34:07.522257Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:35:07.582989Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:36:07.643715Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:37:07.649644Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:38:07.710297Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:39:07.720339Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:40:07.781104Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:41:07.841684Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:42:07.902197Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:43:07.962881Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:44:08.023494Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:45:08.075463Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:46:08.136067Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:47:08.196721Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:48:08.205679Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:49:08.266296Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:50:08.326436Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:51:08.365623Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:52:08.425505Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:53:08.429694Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:54:08.461677Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:55:08.522313Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:56:08.578367Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:57:08.633648Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:58:08.676201Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T17:59:08.718748Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:00:08.735636Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:01:08.780656Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:02:08.817903Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:03:08.877302Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:04:08.937908Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:05:08.997675Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:06:09.057484Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:07:09.118051Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:08:09.178783Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:09:09.237614Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:10:09.298217Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:11:09.325661Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:12:09.386288Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:13:09.446995Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:14:09.500281Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:15:09.517710Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:16:09.525672Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:17:09.586325Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:18:09.647070Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:19:09.707704Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:20:09.718640Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:21:09.731517Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:22:09.770032Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:23:09.819993Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:24:09.880486Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:25:09.941167Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:26:09.996059Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:27:10.056769Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:28:10.117498Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:29:10.157624Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:30:10.174004Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:31:10.234626Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:32:10.253681Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:33:10.285628Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:34:10.346162Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:35:10.349609Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:36:10.410343Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:37:10.413583Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:38:10.462956Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:39:10.498880Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:40:10.558078Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:41:10.578930Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:42:10.637720Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:43:10.698265Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:44:10.758875Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:45:10.819596Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:46:10.880201Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:47:10.921023Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:48:10.957624Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:49:10.986301Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:50:10.997642Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:51:11.058365Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:52:11.085630Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:53:11.146316Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:54:11.207052Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:55:11.267723Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:56:11.277656Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:57:11.309597Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:58:11.355865Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T18:59:11.373534Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:00:11.405611Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:01:11.453217Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:02:11.469712Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:03:11.520599Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:04:11.581289Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:05:11.641734Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:06:11.680012Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:07:11.701294Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:08:11.713416Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:09:11.773986Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:10:11.804944Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:11:11.865533Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:12:11.869673Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:13:11.930280Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:14:11.990911Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:15:12.051502Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:16:12.111712Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:17:12.154952Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:18:12.215576Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:19:12.229650Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:20:12.274626Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:21:12.335241Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:22:12.395999Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:23:12.397704Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:24:12.429611Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:25:12.461698Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:26:12.495506Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:27:12.555581Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:28:12.616231Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:29:12.655045Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:30:12.685631Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:31:12.717725Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:32:12.778435Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:33:12.839067Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:34:12.899816Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:35:12.960512Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:36:13.021234Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:37:13.037753Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:38:13.098457Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:39:13.101678Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:40:13.162406Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:41:13.165687Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:42:13.197540Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:43:13.229707Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:44:13.237660Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:45:13.283899Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:46:13.285685Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:47:13.295396Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:48:13.356116Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:49:13.365643Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:50:13.421709Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:51:13.424742Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:52:13.473664Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:53:13.503407Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:54:13.527229Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:55:13.585756Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:56:13.601606Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:57:13.644085Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:58:13.701571Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T19:59:13.762098Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:00:13.822571Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:01:13.866777Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:02:13.901665Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:03:13.962199Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:04:14.022797Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:05:14.079250Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:06:14.099594Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:07:14.142190Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:08:14.170900Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:09:14.230440Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:10:14.290975Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:11:14.311302Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:12:14.323128Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:13:14.340032Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:14:14.365417Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:15:14.376686Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:16:14.437126Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:17:14.497501Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:18:14.498857Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:19:14.525259Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:20:14.562488Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:21:14.623078Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:22:14.669658Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:23:14.701660Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:24:14.733656Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:25:14.757909Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:26:14.797649Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:27:14.813650Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:28:14.874171Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:29:14.905354Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:30:14.921059Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:31:14.957651Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:32:14.992191Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:33:15.029594Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:34:15.090156Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:35:15.133063Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:36:15.177823Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:37:15.197565Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:38:15.214532Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:39:15.275119Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:40:15.335692Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:41:15.382707Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:42:15.421124Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:43:15.469593Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:44:15.501674Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:45:15.562217Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:46:15.622803Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:47:15.661655Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:48:15.722187Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:49:15.737596Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:50:15.749592Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:51:15.784472Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:52:15.812360Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:53:15.872954Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:54:15.933526Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:55:15.981679Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:56:16.037687Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:57:16.078688Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:58:16.139170Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T20:59:16.180439Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:00:16.240886Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:01:16.301558Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:02:16.333654Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:03:16.365688Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:04:16.373497Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:05:16.429678Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:06:16.488492Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:07:16.493632Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:08:16.553782Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:09:16.613512Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:10:16.661115Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:11:16.721704Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:12:16.779621Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:13:16.799301Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:14:16.848756Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:15:16.909193Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:16:16.969705Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:17:16.984603Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:18:17.022987Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:19:17.066224Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:20:17.126584Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:21:17.127522Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:22:17.142880Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:23:17.149607Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:24:17.204501Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:25:17.219100Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:26:17.277410Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:27:17.313748Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:28:17.374316Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:29:17.434208Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:30:17.437072Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:31:17.497361Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:32:17.553764Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:33:17.614467Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:34:17.671004Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:35:17.731728Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:36:17.733657Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:37:17.773660Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:38:17.820929Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:39:17.881643Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:40:17.933715Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:41:17.994423Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:42:18.055094Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:43:18.115613Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:44:18.176307Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:45:18.237055Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:46:18.297716Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:47:18.358360Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:48:18.418968Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:49:18.479692Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:50:18.509682Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:51:18.570355Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:52:18.631079Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:53:18.691644Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:54:18.751634Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:55:18.812344Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:56:18.872969Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:57:18.933490Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:58:18.981624Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T21:59:19.042261Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:00:19.103044Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:01:19.163735Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:02:19.182276Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:03:19.242987Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:04:19.303678Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:05:19.309665Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:06:19.370291Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:07:19.430417Z | Info | Live bytes: 1685.65MB Heap size: 4145.02MB +2024-07-18T22:07:52.801560Z | Error | Got EOF +2024-07-19 07:09:01.5220000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-19 07:09:01.5240000 [client] INFO Finding haskell-language-server +2024-07-19 07:09:01.5270000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:01.5270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:01.5360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-19 07:09:01.9110000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:01.9110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:01.9200000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-19 07:09:02.2100000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:02.2110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:02.2170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-19 07:09:02.4860000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:02.4860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:02.4920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-19 07:09:02.6940000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:02.6940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:02.7010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-19 07:09:02.7160000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:02.7160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:02.7220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-19 07:09:02.7470000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:02.7470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:02.7530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-19 07:09:02.7790000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-19 07:09:02.9270000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:02.9270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:02.9330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-19 07:09:03.1290000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-19 07:09:03.1300000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-19 07:09:13.0300000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-19 07:09:13.2480000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-19 07:09:13.2490000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:13.2490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:13.2530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-19 07:09:13.3380000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:13.3380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:13.3440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-19 07:09:13.3610000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:13.3610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:13.3650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-19 07:09:13.3790000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:13.3790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:13.3840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-19 07:09:13.3990000 [client] INFO Checking for ghcup installation +2024-07-19 07:09:13.3990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-19 07:09:13.4040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-19 07:09:13.5210000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-19 07:09:13.5220000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-19 07:09:13.5220000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-19 07:09:13.5220000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-19 07:09:13.5220000 [client] INFO server environment variables: +2024-07-19 07:09:13.5230000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-19 07:09:13.5230000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-19 07:09:13.5230000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-19 07:09:13.5270000 [client] INFO Starting language server +2024-07-19T07:09:53.657937Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-19T07:09:53.658807Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-19T07:09:53.658977Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-19T07:09:53.661206Z | Info | Logging heap statistics every 60.00s +2024-07-19T07:09:53.668752Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-19T07:09:53.669139Z | Info | Starting server +2024-07-19T07:09:53.671064Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-19T07:09:53.792375Z | Info | Started LSP server in 0.12s +2024-07-19T07:09:55.045795Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-19T07:09:55.046794Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-19T07:09:55.550928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T07:09:56.447846Z | Info | Load cabal cradle using single file +2024-07-19T07:09:57.377203Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT18165-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-19T07:10:05.149822Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-19T07:10:05.155487Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-19T07:10:05.478017Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-19T07:10:05.478539Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-19T07:10:06.725122Z | Info | Load cabal cradle using single file +2024-07-19T07:10:07.680162Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT18165-1 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-19T07:10:11.216090Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-19T07:10:11.216470Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-19T07:10:11.223218Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-19T07:10:11.641449Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Tx.hs +2024-07-19T07:10:11.641919Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-19T07:10:12.985649Z | Info | Load cabal cradle using single file +2024-07-19T07:10:14.021001Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT18165-2 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-19T07:10:17.807350Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-19T07:10:17.808374Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-19T07:10:17.808876Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-19T07:10:17.814539Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-19T07:10:32.179452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T07:10:53.681633Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:11:53.742088Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:12:53.794765Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:13:53.855697Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:14:53.915608Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:15:53.976253Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:16:54.037504Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:17:54.084020Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:18:54.130925Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:19:54.167623Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:20:54.228914Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:21:54.290413Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:22:54.322811Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:23:54.384121Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:24:54.444508Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:25:54.505119Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:26:54.516712Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:27:54.522327Z | Info | Live bytes: 622.33MB Heap size: 2245.00MB +2024-07-19T07:28:54.553755Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:29:54.607250Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:30:54.667964Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:31:54.728967Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:32:54.789933Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:33:54.850767Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:34:54.911916Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:35:54.913303Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:36:54.974256Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:37:55.034532Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:38:55.095209Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:39:55.155697Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:40:55.215498Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:41:55.275473Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:42:55.336107Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:43:55.343723Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:44:55.403573Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:45:55.463490Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:46:55.523490Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:47:55.584381Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:48:55.602405Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:49:55.662550Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:50:55.723339Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:51:55.784172Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:52:55.844441Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:53:55.866527Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:54:55.926615Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:55:55.986555Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:56:56.017739Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:57:56.077542Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:58:56.138607Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T07:59:56.194911Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:00:56.256483Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:01:56.258925Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:02:56.308673Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:03:56.369902Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:04:56.426827Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:05:56.441298Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:06:56.444484Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:07:56.450748Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:08:56.466245Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:09:56.472765Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:10:56.533962Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:11:56.578891Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:12:56.635763Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:13:56.685991Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:14:56.710287Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:15:56.771789Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:16:56.795674Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:17:56.856944Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:18:56.918157Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:19:56.979418Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:20:57.040640Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:21:57.101911Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:22:57.122710Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:23:57.183862Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:24:57.199775Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:25:57.213904Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:26:57.251071Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:27:57.312825Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:28:57.373967Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:29:57.431857Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:30:57.493643Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:31:57.554923Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:32:57.588654Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:33:57.616035Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:34:57.634940Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:35:57.696513Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:36:57.757850Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:37:57.819322Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:38:57.849503Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:39:57.910849Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:40:57.954789Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:41:58.016041Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:42:58.019621Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:43:58.057560Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:44:58.118602Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:45:58.153860Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:46:58.184465Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:47:58.245887Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:48:58.274884Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:49:58.277220Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:50:58.296656Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:51:58.306949Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:52:58.353320Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T08:53:58.370749Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T09:29:49.613124Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T09:30:49.673829Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T09:31:49.699452Z | Info | Live bytes: 639.57MB Heap size: 2245.00MB +2024-07-19T09:32:49.717463Z | Info | Live bytes: 663.05MB Heap size: 2245.00MB +2024-07-19T09:33:49.758388Z | Info | Live bytes: 663.05MB Heap size: 2245.00MB +2024-07-19T09:34:49.816104Z | Info | Live bytes: 663.05MB Heap size: 2245.00MB +2024-07-19T09:35:49.849326Z | Info | Live bytes: 663.05MB Heap size: 2245.00MB +2024-07-19T09:36:49.909555Z | Info | Live bytes: 663.05MB Heap size: 2245.00MB +2024-07-19T09:37:27.587361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:37:29.012906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:37:49.423561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:37:49.911221Z | Info | Live bytes: 788.05MB Heap size: 2245.00MB +2024-07-19T09:37:50.813745Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Value.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/StakePoolMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Address.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/DRepMetadata.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-07-19T09:37:50.852824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:38:02.331967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:38:14.145184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:38:15.686686Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-19T09:38:20.087741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:38:20.091208Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-19T09:38:24.842031Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-19T09:38:24.853216Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:38:29.873846Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-19T09:38:29.990183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:38:33.308660Z | Info | LSP: received shutdown +2024-07-19T09:38:33.310755Z | Error | Got EOF +2024-07-19T09:39:46.001573Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-19T09:39:46.002522Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-19T09:39:46.002731Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-19T09:39:46.005129Z | Info | Logging heap statistics every 60.00s +2024-07-19T09:39:46.011536Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-19T09:39:46.011899Z | Info | Starting server +2024-07-19T09:39:46.013323Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-19T09:39:46.051116Z | Info | Started LSP server in 0.04s +2024-07-19T09:39:47.259607Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-07-19T09:39:47.260171Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-19T09:39:47.751822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:39:48.671322Z | Info | Load cabal cradle using single file +2024-07-19T09:39:49.594560Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT161752-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-19T09:39:57.518440Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-19T09:39:57.522764Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-19T09:40:13.418535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:13.938663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:18.300561Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:18.943302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:20.186420Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-19T09:40:20.588236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:22.065134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:23.305748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:29.562716Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-19T09:40:46.019198Z | Info | Live bytes: 996.79MB Heap size: 2657.09MB +2024-07-19T09:40:52.884509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:40:54.698240Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-19T09:41:46.032895Z | Info | Live bytes: 1252.13MB Heap size: 2657.09MB +2024-07-19T09:42:17.023469Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:42:17.716587Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:42:46.046517Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:43:46.099553Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:44:46.160806Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:45:46.169764Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:46:46.213313Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:47:46.266336Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:48:46.304542Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:49:46.364275Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:50:46.368286Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:51:46.373114Z | Info | Live bytes: 712.59MB Heap size: 2948.60MB +2024-07-19T09:51:52.681805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:06.000205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:12.693501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:14.025511Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:15.047976Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:15.595668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:19.925833Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-19T09:52:19.926345Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-19T09:52:20.036325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:22.337023Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:22.762850Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" +2024-07-19T09:52:22.871512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:24.386819Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/TxMetadata.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ScriptData.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" ] +2024-07-19T09:52:24.603239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:26.488419Z | Info | Load cabal cradle using single file +2024-07-19T09:52:27.652359Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT161752-25 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-19T09:52:33.113467Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T09:52:46.384806Z | Info | Live bytes: 1187.94MB Heap size: 2948.60MB +2024-07-19T09:53:46.445236Z | Info | Live bytes: 1187.94MB Heap size: 2948.60MB +2024-07-19T09:53:49.026097Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-9e21f019e6dcd9c3293d5ee7ef25ace2416b37d9 +2024-07-19T09:53:49.026323Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-9e21f019e6dcd9c3293d5ee7ef25ace2416b37d9 +2024-07-19T09:53:49.032761Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.0.0.0-inplace + , cardano-api-9.0.0.0-inplace-internal ] +2024-07-19T09:54:46.497258Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T09:55:46.538685Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T09:56:46.559494Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T09:57:46.579355Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T09:58:46.640359Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T09:59:46.680731Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T10:00:46.682071Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T10:01:46.689456Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T10:02:46.740793Z | Info | Live bytes: 1091.62MB Heap size: 3009.41MB +2024-07-19T10:02:49.911126Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T10:03:46.763553Z | Info | Live bytes: 1186.19MB Heap size: 3009.41MB +2024-07-19T10:04:46.802060Z | Info | Live bytes: 1186.19MB Heap size: 3009.41MB +2024-07-19T10:05:46.862842Z | Info | Live bytes: 1186.19MB Heap size: 3009.41MB +2024-07-19T10:06:46.873613Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:07:46.908274Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:08:46.915560Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:09:46.976240Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:10:47.037002Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:11:47.097303Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:12:47.158376Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:13:47.219450Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:14:47.280442Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:15:47.340083Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:16:47.400815Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:17:47.422578Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:18:47.482216Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:19:47.542824Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:20:47.603807Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:21:47.664737Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:22:47.725440Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:23:47.781300Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:24:47.842253Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:25:47.902660Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:26:47.963954Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:27:48.025069Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:28:48.052241Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:29:48.112991Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:30:48.163399Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:31:48.224291Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:32:48.244171Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:33:48.304095Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:34:48.364300Z | Info | Live bytes: 1448.17MB Heap size: 3009.41MB +2024-07-19T10:35:31.360783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T10:35:48.368165Z | Info | Live bytes: 1520.08MB Heap size: 3009.41MB +2024-07-19T10:36:48.380158Z | Info | Live bytes: 1520.08MB Heap size: 3009.41MB +2024-07-19T10:37:48.420122Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:38:48.480952Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:39:48.535171Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:40:48.595318Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:41:48.619696Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:42:48.680406Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:43:48.695250Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:44:48.756182Z | Info | Live bytes: 1530.17MB Heap size: 3009.41MB +2024-07-19T10:45:48.817210Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:46:48.863965Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:47:48.924912Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:48:48.985697Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:49:49.046275Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:50:49.085424Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:51:49.146594Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:52:49.165495Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:53:49.183553Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:54:49.244500Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:55:49.278057Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:56:49.338298Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:57:49.398770Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:58:49.459850Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T10:59:49.521092Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T11:00:49.582151Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T11:01:49.643232Z | Info | Live bytes: 1539.56MB Heap size: 3009.41MB +2024-07-19T11:02:12.276031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:02:49.675368Z | Info | Live bytes: 1078.21MB Heap size: 3515.88MB +2024-07-19T11:03:49.735976Z | Info | Live bytes: 1078.21MB Heap size: 3515.88MB +2024-07-19T11:04:49.796251Z | Info | Live bytes: 1078.21MB Heap size: 3515.88MB +2024-07-19T11:05:49.856882Z | Info | Live bytes: 1078.21MB Heap size: 3515.88MB +2024-07-19T11:05:52.279006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:05.247420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:31.935431Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:33.078580Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:33.739509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:34.612170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:35.136751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:37.647425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:38.264729Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:38.914980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:06:40.231038Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Sign.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Case.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToMaryEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Types.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToBabbageEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAlonzoEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyToAllegraEra.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ShelleyEraOnly.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/MaryEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/ConwayEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/BabbageEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AlonzoEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eon/AllegraEraOnwards.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Certificate.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Value.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Ledger/Lens.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/VotingProcedure.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/ProposalProcedure.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/ProtocolParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Address.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Feature.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/GenesisParameters.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Block.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/SerialiseLedgerCddl.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query/Expr.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/LedgerState.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Shelley.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/Version.hs" ] +2024-07-19T11:06:49.858090Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:07:49.877027Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:08:49.937168Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:09:49.972219Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:10:50.019562Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:11:50.066271Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:12:50.126366Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:13:50.169268Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:14:50.171432Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:15:50.232304Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:16:50.293655Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:17:50.307591Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:18:50.359201Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:19:50.371633Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:20:50.433332Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:21:50.494465Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:22:50.555956Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:23:50.617324Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:24:50.678686Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:25:50.739905Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:26:50.801001Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:27:50.857355Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:28:50.918133Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:29:50.978261Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:30:51.038820Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:31:51.078892Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:32:51.139178Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:33:51.163121Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:34:51.223155Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:35:51.283911Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:36:51.299316Z | Info | Live bytes: 1462.94MB Heap size: 3515.88MB +2024-07-19T11:37:23.051278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T11:37:51.326266Z | Info | Live bytes: 1537.67MB Heap size: 3515.88MB +2024-07-19T11:38:51.387433Z | Info | Live bytes: 1537.67MB Heap size: 3515.88MB +2024-07-19T11:39:51.448078Z | Info | Live bytes: 1537.67MB Heap size: 3515.88MB +2024-07-19T11:40:51.505272Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:41:51.529949Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:42:51.590903Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:43:51.651351Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:44:51.712350Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:45:51.752925Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:46:51.783869Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:47:51.844183Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:48:51.904930Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:49:51.918172Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:50:51.939453Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:51:51.955261Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:52:52.016559Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:53:52.067295Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:54:52.128239Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:55:52.189352Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:56:52.249926Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:57:52.306505Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:58:52.367753Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T11:59:52.428583Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T12:00:52.489311Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T12:01:52.503360Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T12:02:52.563324Z | Info | Live bytes: 1550.31MB Heap size: 3515.88MB +2024-07-19T12:03:47.778318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T12:03:52.565197Z | Info | Live bytes: 1562.65MB Heap size: 3515.88MB +2024-07-19T12:04:52.625287Z | Info | Live bytes: 1562.65MB Heap size: 3515.88MB +2024-07-19T12:05:52.685323Z | Info | Live bytes: 1562.65MB Heap size: 3515.88MB +2024-07-19T12:06:52.746466Z | Info | Live bytes: 1562.65MB Heap size: 3515.88MB +2024-07-19T12:07:52.807358Z | Info | Live bytes: 1562.65MB Heap size: 3515.88MB +2024-07-19T12:08:28.877851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T12:08:52.827006Z | Info | Live bytes: 1612.51MB Heap size: 3515.88MB +2024-07-19T12:09:52.887685Z | Info | Live bytes: 1612.51MB Heap size: 3515.88MB +2024-07-19T12:10:52.948210Z | Info | Live bytes: 1612.51MB Heap size: 3515.88MB +2024-07-19T12:11:53.009266Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:12:53.070212Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:13:53.079842Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:14:53.083998Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:40:02.056473Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:41:02.065287Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:42:02.126137Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:43:02.134575Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:44:02.182499Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:45:02.243509Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:46:02.303567Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:47:02.340966Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:48:02.400590Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:49:02.419780Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:50:02.480871Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:51:02.541692Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:52:02.547231Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:53:02.591396Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:54:02.640932Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:55:02.702163Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:56:02.712540Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:57:02.760530Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:58:02.821999Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T12:59:02.883324Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:00:02.898550Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:01:02.923826Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:02:02.948602Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:03:02.971159Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:04:02.998622Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:05:03.051753Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:06:03.110183Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:07:03.132398Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:08:03.193296Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:09:03.253596Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:10:03.314602Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:11:03.364918Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:12:03.417280Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:13:03.478238Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:14:03.501489Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:15:03.562511Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:16:03.615582Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:17:03.675571Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:18:03.735751Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:19:03.796603Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:20:03.810283Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:21:03.867802Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:22:03.928963Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:23:03.979029Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:24:04.039572Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:25:04.058507Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:26:04.118584Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:27:04.160467Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:28:04.220510Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:29:04.250727Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:30:04.311580Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:31:04.315559Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:32:04.333558Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:33:04.351747Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:34:04.412289Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:35:04.455718Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:36:04.516701Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:37:04.577559Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:38:04.638272Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:39:04.686547Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:40:04.746641Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:41:04.807595Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:42:04.835692Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:43:04.840639Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:44:04.858729Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:45:04.872322Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:46:04.933509Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:47:04.994300Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:48:05.056186Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:49:05.068651Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:50:05.129664Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:51:05.190311Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:52:05.250599Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:53:05.310544Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:54:05.371059Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:55:05.382434Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:56:05.443472Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:57:05.474746Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:58:05.487521Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T13:59:05.527573Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:00:05.588402Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:01:05.610271Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:02:05.661299Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:03:05.722031Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:04:05.746894Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:05:05.807509Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:06:05.817716Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:07:05.878433Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:08:05.890897Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:09:05.908857Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:10:05.910523Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:11:05.971417Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:12:06.031406Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:13:06.091678Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:14:06.151575Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:15:06.212592Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:16:06.233860Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:17:06.238242Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:18:06.298690Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:19:06.328432Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:20:06.389317Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:21:06.449584Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:22:06.509621Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:23:06.520462Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:24:06.580658Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:25:06.641679Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:26:06.701617Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:27:06.761482Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:28:06.822067Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:29:06.827628Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:30:06.887622Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:31:06.947669Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:32:07.008479Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:33:07.068517Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:34:07.129093Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:35:07.190689Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:36:07.250591Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:37:07.311085Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:38:07.335714Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:39:07.351318Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:40:07.411510Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:41:07.444244Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:42:07.497133Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:43:07.511507Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:44:07.523642Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:45:07.584411Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:46:07.644593Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:47:07.705507Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:48:07.762471Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:49:07.823452Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:50:07.861051Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:51:07.921501Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:52:07.982289Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:53:07.987688Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:54:08.048486Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:55:08.109105Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:56:08.169805Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:57:08.230262Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:58:08.274442Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T14:59:08.277663Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:00:08.317900Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:01:08.358996Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:02:08.419748Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:03:08.479533Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:04:08.539943Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:05:08.599612Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:06:08.659534Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:07:08.719659Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:08:08.780453Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:09:08.840576Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:10:08.900578Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:11:08.960564Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:12:09.020623Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:13:09.040058Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:14:09.054208Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:15:09.114706Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:16:09.131141Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:17:09.153608Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:18:09.214520Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:19:09.243622Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:20:09.303518Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:21:09.328597Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:22:09.363000Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:23:09.417880Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:24:09.436253Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:25:09.496909Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:26:09.557440Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:27:09.611625Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:28:09.635646Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:29:09.695478Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:30:09.755576Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:31:09.813718Z | Info | Live bytes: 1613.23MB Heap size: 3515.88MB +2024-07-19T15:31:35.281350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T15:32:09.847638Z | Info | Live bytes: 1628.52MB Heap size: 3515.88MB +2024-07-19T15:33:09.908449Z | Info | Live bytes: 1628.52MB Heap size: 3515.88MB +2024-07-19T15:34:09.969411Z | Info | Live bytes: 1628.52MB Heap size: 3515.88MB +2024-07-19T15:35:10.017754Z | Info | Live bytes: 1628.52MB Heap size: 3515.88MB +2024-07-19T15:36:10.077670Z | Info | Live bytes: 1628.52MB Heap size: 3515.88MB +2024-07-19T15:37:10.137583Z | Info | Live bytes: 1628.52MB Heap size: 3515.88MB +2024-07-19T15:37:24.396000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T15:38:10.180481Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:39:10.240577Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:40:10.300524Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:41:10.361062Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:42:10.421524Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:43:10.468871Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:44:10.528653Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:45:10.588685Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:46:10.649369Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:47:10.709474Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:48:10.769489Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:49:10.829527Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:50:10.890045Z | Info | Live bytes: 1633.02MB Heap size: 3515.88MB +2024-07-19T15:50:20.273021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T15:51:09.034739Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T15:51:10.891092Z | Info | Live bytes: 2061.45MB Heap size: 3515.88MB +2024-07-19T15:51:21.490657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-19T15:52:10.939892Z | Info | Live bytes: 2099.38MB Heap size: 3515.88MB +2024-07-19T15:53:10.999662Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T15:54:11.060445Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T15:55:11.121134Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T15:56:11.160633Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T15:57:11.200715Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T15:58:11.237823Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T15:59:11.298191Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:00:11.343439Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:01:11.404356Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:02:11.464646Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:03:11.499478Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:04:11.515589Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:05:11.557705Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:06:11.582310Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:07:11.598855Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:08:11.622430Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:09:11.683448Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:10:11.687587Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:11:11.747533Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:12:11.762444Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:13:11.775753Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:14:11.836699Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:15:11.874094Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:16:11.932632Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:17:11.980151Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:18:12.013927Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:19:12.063018Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:20:12.123513Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:21:12.183583Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:22:12.224867Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:23:12.246173Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:24:12.306639Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:25:12.322680Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:26:12.339680Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:27:12.353044Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:28:12.411985Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:29:12.472468Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:30:12.533165Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:31:12.561569Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:32:12.575612Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:33:12.608866Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:34:12.669795Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:35:12.730666Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:36:12.790540Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:37:12.811087Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:38:12.871516Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:39:12.931402Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:40:12.991432Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:41:13.051739Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:42:13.113040Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:43:13.173995Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:44:13.235072Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:45:13.253563Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:46:13.291328Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:47:13.352273Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:48:13.395688Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:49:13.456959Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:50:13.518589Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:51:13.579778Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:52:13.640824Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:53:13.701867Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:54:13.762494Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:55:13.768990Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:56:13.779258Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:57:13.840280Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:58:13.901416Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T16:59:13.962241Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:00:14.002119Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:01:14.027059Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:02:14.051689Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:03:14.112483Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:04:14.172624Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:05:14.186371Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:06:14.238161Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:07:14.288959Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:08:14.294006Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:09:14.314320Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:10:14.375248Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:11:14.436304Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:12:14.497144Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:13:14.513726Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:14:14.574480Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:15:14.581164Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:16:14.593639Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:17:14.654609Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:18:14.700197Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:19:14.761412Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:20:14.791626Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:21:14.852673Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:22:14.913642Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:23:14.973471Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:24:15.033531Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:25:15.066514Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:26:15.126665Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:27:15.183542Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:28:15.208505Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:29:15.269265Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:30:15.329580Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:31:15.380323Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:32:15.440619Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:33:15.500614Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:34:15.546220Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:35:15.556573Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:36:15.570386Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:37:15.590496Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:38:15.651486Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:39:15.681375Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:40:15.742277Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:41:15.803143Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:42:15.863844Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:43:15.924774Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:44:15.985717Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:45:16.045616Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:46:16.072709Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:47:16.132432Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:48:16.135082Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:49:16.195936Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:50:16.256957Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:51:16.259939Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:52:16.291140Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:53:16.315276Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:54:16.367640Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:55:16.381037Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:56:16.441897Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:57:16.502479Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:58:16.562523Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T17:59:16.622450Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:00:16.680537Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:01:16.740398Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:02:16.800754Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:03:16.860440Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:04:16.920510Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:05:16.980636Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:06:17.040924Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:07:17.100486Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:08:17.160672Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:09:17.220464Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:10:17.247484Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:11:17.307445Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:12:17.367509Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:13:17.427430Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:14:17.487474Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:15:17.547511Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:16:17.607466Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:17:17.667401Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:18:17.727584Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:19:17.788630Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:20:17.849642Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:21:17.881534Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:22:17.910887Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:23:17.971631Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:24:18.032572Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:25:18.093259Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:26:18.113106Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:27:18.168616Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:28:18.228555Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:29:18.289450Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:30:18.310536Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:31:18.368592Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:32:18.421539Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:33:18.481546Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:34:18.542411Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:35:18.563988Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:36:18.623456Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:37:18.683762Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:38:18.744930Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:39:18.805860Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:40:18.827868Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:41:18.888743Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:42:18.917262Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:43:18.919162Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:44:18.947966Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:45:19.008653Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:46:19.068576Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:47:19.073536Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:48:19.134188Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:49:19.163719Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:50:19.223662Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:51:19.284215Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:52:19.328489Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:53:19.388717Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:54:19.449749Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:55:19.510652Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:56:19.536953Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:57:19.598045Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:58:19.603318Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T18:59:19.663624Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:00:19.724514Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:01:19.784538Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:02:19.844706Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:03:19.905585Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:04:19.936296Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:05:19.991185Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:06:20.020072Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:07:20.081056Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:08:20.090469Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:09:20.124547Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:10:20.141961Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:11:20.174412Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:12:20.235356Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:13:20.253799Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:14:20.314588Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:15:20.374532Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:16:20.384097Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:17:20.445149Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:18:20.498446Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:19:20.559449Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:20:20.617970Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:21:20.633433Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:22:20.693695Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:23:20.695977Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:24:20.756886Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:25:20.817529Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:26:20.877468Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:27:20.879556Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:28:20.936635Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:29:20.952240Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:30:21.013271Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:31:21.015887Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:32:21.076805Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:33:21.127027Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:34:21.152097Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:35:21.182651Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:36:21.242543Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:37:21.291116Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:38:21.352179Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:39:21.412866Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:40:21.473750Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:41:21.533489Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:42:21.587953Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:43:21.648830Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:44:21.656798Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:45:21.674166Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:46:21.678217Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:47:21.690352Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:48:21.740610Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:49:21.752937Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:50:21.764640Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:51:21.816897Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:52:21.877871Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:53:21.891773Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:54:21.953264Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:55:22.014263Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:56:22.074576Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:57:22.135556Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:58:22.195419Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T19:59:22.255919Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:00:22.307458Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:01:22.311739Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:02:22.372765Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:03:22.386635Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:04:22.446587Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:05:22.504686Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:06:22.518566Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:07:22.579585Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:08:22.627681Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:09:22.687484Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:10:22.747603Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:11:22.808434Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:12:22.868603Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:13:22.922254Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:14:22.932020Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:15:22.993109Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:16:22.998118Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:17:23.059039Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:18:23.090446Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:19:23.147408Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:31:41.299500Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:32:41.340944Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:33:41.401392Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:34:41.461478Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:35:41.521746Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:36:41.534497Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:37:41.573940Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:38:41.584263Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:39:41.644616Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:40:41.664231Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:41:41.724629Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:42:41.784616Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:43:41.844509Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:44:41.905333Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:45:41.951846Z | Info | Live bytes: 2106.68MB Heap size: 3515.88MB +2024-07-19T20:46:16.598074Z | Info | LSP: received shutdown +2024-07-19T20:46:16.600346Z | Error | Got EOF +2024-07-19T20:46:16.600463Z | Info | Reactor thread stopped +2024-07-20 07:12:25.3020000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-20 07:12:25.3050000 [client] INFO Finding haskell-language-server +2024-07-20 07:12:25.3080000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:25.3080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:25.3220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-20 07:12:25.8190000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:25.8190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:25.8310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-20 07:12:26.2550000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:26.2550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:26.2680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-20 07:12:26.5310000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:26.5320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:26.5410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-20 07:12:26.7950000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:26.7950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:26.8000000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-20 07:12:26.8170000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:26.8170000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:26.8250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-20 07:12:26.8420000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:26.8420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:26.8490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-20 07:12:26.8860000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-20 07:12:27.0960000 [client] INFO Checking for ghcup installation +2024-07-20 07:12:27.0960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-20 07:12:27.1080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-21 05:50:19.3520000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-21 05:50:19.3630000 [client] INFO Finding haskell-language-server +2024-07-21 05:50:19.3650000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:19.3660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:19.3740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-21 05:50:19.8710000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:19.8710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:19.8770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-21 05:50:19.9930000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:19.9930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:19.9990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-21 05:50:20.1040000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:20.1040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:20.1100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-21 05:50:20.2320000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:20.2320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:20.2360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-21 05:50:20.2510000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:20.2510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:20.2560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-21 05:50:20.2710000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:20.2710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:20.2760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-21 05:50:20.2960000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-21 05:50:20.3340000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:20.3340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:20.3390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-21 05:50:20.4450000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-21 05:50:20.4450000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-21 05:50:31.6870000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-21 05:50:31.9820000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-21 05:50:31.9820000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:31.9820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:31.9870000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-21 05:50:32.0710000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:32.0720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:32.0770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-21 05:50:32.0940000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:32.0940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:32.0990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-21 05:50:32.1130000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:32.1130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:32.1180000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-21 05:50:32.1310000 [client] INFO Checking for ghcup installation +2024-07-21 05:50:32.1310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 05:50:32.1360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-21 05:50:32.2320000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-21 05:50:32.2320000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-21 05:50:32.2320000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-21 05:50:32.2330000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-21 05:50:32.2330000 [client] INFO server environment variables: +2024-07-21 05:50:32.2330000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-21 05:50:32.2330000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-21 05:50:32.2330000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-21 05:50:32.2340000 [client] INFO Starting language server +2024-07-21T05:50:42.077662Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-21T05:50:42.078975Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-21T05:50:42.079468Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-21T05:50:42.086937Z | Info | Logging heap statistics every 60.00s +2024-07-21T05:50:42.103076Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-21T05:50:42.103559Z | Info | Starting server +2024-07-21T05:50:42.104965Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-21T05:50:42.174300Z | Info | Started LSP server in 0.07s +2024-07-21T05:50:43.555895Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Value.hs +2024-07-21T05:50:43.557367Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-21T05:50:44.047907Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T05:50:45.124599Z | Info | Load cabal cradle using single file +2024-07-21T05:50:46.157008Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT15859-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-21T05:50:49.907336Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-21T05:50:49.911924Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-21T05:51:42.132682Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:52:42.192708Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:53:42.252479Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:54:42.313286Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:55:42.373581Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:56:42.402921Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:57:42.463451Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:58:42.486722Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T05:59:42.546565Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:00:42.607120Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:01:42.667561Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:02:42.728076Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:03:42.758446Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:04:42.819116Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:05:42.879657Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:06:42.940207Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:07:43.000785Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:08:43.061504Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:09:43.122084Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:10:43.149756Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:11:43.210343Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:12:43.270949Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:13:43.331526Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:14:43.392120Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:15:43.397705Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:16:43.444755Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:17:43.505187Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:18:43.557812Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:19:43.578588Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:20:43.639351Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:21:43.700526Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:22:43.761258Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:23:43.822310Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:24:43.883565Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:25:43.944711Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:26:43.955042Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:27:43.979658Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:28:43.985302Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:29:44.045559Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:30:44.106327Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:31:44.167497Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:32:44.198239Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:33:44.202521Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:34:44.210105Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:35:44.228629Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:36:44.289431Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:37:44.338661Z | Info | Live bytes: 623.19MB Heap size: 1797.26MB +2024-07-21T06:38:21.022156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T06:38:44.357695Z | Info | Live bytes: 682.67MB Heap size: 2202.01MB +2024-07-21T06:39:09.480590Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T06:39:44.390549Z | Info | Live bytes: 735.74MB Heap size: 2202.01MB +2024-07-21T06:40:44.450536Z | Info | Live bytes: 740.13MB Heap size: 2202.01MB +2024-07-21T06:41:44.462259Z | Info | Live bytes: 740.13MB Heap size: 2202.01MB +2024-07-21T06:42:44.493967Z | Info | Live bytes: 740.13MB Heap size: 2202.01MB +2024-07-21T06:43:44.555425Z | Info | Live bytes: 740.13MB Heap size: 2202.01MB +2024-07-21T06:44:44.615672Z | Info | Live bytes: 740.13MB Heap size: 2202.01MB +2024-07-21T06:45:44.630738Z | Info | Live bytes: 740.13MB Heap size: 2202.01MB +2024-07-21T06:46:44.638287Z | Info | Live bytes: 740.13MB Heap size: 2202.01MB +2024-07-21T06:47:36.365103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T06:47:41.756603Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T06:47:44.646379Z | Info | Live bytes: 766.45MB Heap size: 2202.01MB +2024-07-21T06:48:33.895256Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T06:48:44.707158Z | Info | Live bytes: 785.29MB Heap size: 2202.01MB +2024-07-21T06:49:44.768138Z | Info | Live bytes: 797.26MB Heap size: 2202.01MB +2024-07-21T06:50:44.828545Z | Info | Live bytes: 797.26MB Heap size: 2202.01MB +2024-07-21T06:51:44.889195Z | Info | Live bytes: 809.35MB Heap size: 2202.01MB +2024-07-21T06:52:44.950313Z | Info | Live bytes: 809.35MB Heap size: 2202.01MB +2024-07-21T06:53:45.011453Z | Info | Live bytes: 809.35MB Heap size: 2202.01MB +2024-07-21T06:54:45.035775Z | Info | Live bytes: 809.35MB Heap size: 2202.01MB +2024-07-21T06:55:45.039482Z | Info | Live bytes: 809.35MB Heap size: 2202.01MB +2024-07-21T06:56:38.515419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T06:56:45.100609Z | Info | Live bytes: 809.35MB Heap size: 2202.01MB +2024-07-21T06:57:45.161726Z | Info | Live bytes: 817.74MB Heap size: 2202.01MB +2024-07-21T06:58:45.222571Z | Info | Live bytes: 817.74MB Heap size: 2202.01MB +2024-07-21T06:59:10.019258Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T06:59:45.283799Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:00:45.332399Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:01:45.393046Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:02:45.453813Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:03:45.462557Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:04:45.522569Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:05:45.583652Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:06:45.645126Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:07:45.678037Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:08:45.739549Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:09:45.757045Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:10:45.773753Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:11:45.834643Z | Info | Live bytes: 838.81MB Heap size: 2202.01MB +2024-07-21T07:12:04.055011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T07:12:45.895797Z | Info | Live bytes: 838.93MB Heap size: 2202.01MB +2024-07-21T07:12:52.394179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T07:13:45.957120Z | Info | Live bytes: 851.82MB Heap size: 2202.01MB +2024-07-21T07:14:46.018371Z | Info | Live bytes: 851.82MB Heap size: 2202.01MB +2024-07-21T07:15:46.079247Z | Info | Live bytes: 868.72MB Heap size: 2202.01MB +2024-07-21T07:16:46.140554Z | Info | Live bytes: 868.72MB Heap size: 2202.01MB +2024-07-21T07:17:46.183335Z | Info | Live bytes: 871.25MB Heap size: 2202.01MB +2024-07-21T07:18:00.063647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T07:18:03.234319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T07:18:46.227687Z | Info | Live bytes: 900.26MB Heap size: 2202.01MB +2024-07-21T07:19:46.268245Z | Info | Live bytes: 900.26MB Heap size: 2202.01MB +2024-07-21T07:20:46.329120Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:21:46.381785Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:22:46.443183Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:23:46.474211Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:24:46.484272Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:25:46.545717Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:26:46.607176Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:27:46.668894Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:28:46.730517Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:29:46.792345Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:30:46.797948Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:31:46.859315Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:32:46.882754Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:33:46.943831Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:34:46.985599Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:35:47.045785Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:36:47.087745Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:37:47.148657Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:38:47.150776Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:39:47.211366Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:40:47.272251Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:41:47.332727Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:42:47.346210Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:43:47.361224Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:44:47.396603Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:45:47.457363Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:46:47.517609Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:47:47.578222Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:48:47.638705Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:49:47.698629Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:50:47.758665Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:51:47.796460Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:52:47.856495Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:53:47.902689Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:54:47.962709Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:55:47.990679Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:56:48.027602Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:57:48.052372Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:58:48.112557Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T07:59:48.172585Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:00:48.232776Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:01:48.235249Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:02:48.256883Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:03:48.317642Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:04:48.367555Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:05:48.428332Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:06:48.462089Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:07:48.489289Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:08:48.550268Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:09:48.610611Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:10:48.649145Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:11:48.709561Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:12:48.769640Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:13:48.830368Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:14:48.891215Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:15:48.933619Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:16:48.979352Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:17:49.040282Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:18:49.100568Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:19:49.116887Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:20:49.177753Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:21:49.237585Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:22:49.298429Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:23:49.339636Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:24:49.399651Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:25:49.457654Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:26:49.518621Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:27:49.578725Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:28:49.638606Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:29:49.661608Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:30:49.722419Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:31:49.725838Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:32:49.787204Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:33:49.848509Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:34:49.897689Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:35:49.958657Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:36:50.019559Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:37:50.080332Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:38:50.125832Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:39:50.170515Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:40:50.231657Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:41:50.289806Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:42:50.301930Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:43:50.336338Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:44:50.363916Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:45:50.424930Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:46:50.486471Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:47:50.547004Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:48:50.561145Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:49:50.622503Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:50:50.683520Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:51:50.744202Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:52:50.770167Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:53:50.830686Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:54:50.890685Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:55:50.951565Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:56:50.957829Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:57:51.018823Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:58:51.079784Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T08:59:51.140507Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:00:51.199746Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:01:51.245962Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:02:51.306544Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:03:51.367643Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:04:51.429018Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:05:51.489987Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:06:51.533915Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:07:51.561490Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:08:51.622769Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:09:51.674606Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:10:51.730214Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:11:51.758007Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:12:51.773686Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:13:51.808868Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:14:51.865587Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:15:51.926069Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:16:51.985518Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:17:51.999682Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:18:52.038001Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:19:52.099313Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:20:52.159704Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:21:52.219624Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:22:52.277950Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:23:52.292143Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:24:52.302163Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:25:52.363715Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:26:52.424994Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:27:52.486246Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:28:52.547351Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:29:52.608517Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:30:52.669629Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:31:52.730713Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:32:52.791964Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:33:52.853308Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:34:52.913607Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:35:52.974617Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:36:53.004272Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:37:53.064854Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:38:53.075517Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:39:53.112701Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:40:53.173802Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:41:53.234587Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:42:53.259837Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:43:53.320724Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:44:53.362152Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:45:53.422490Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:46:53.482975Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:47:53.542512Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:48:53.581686Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:49:53.641566Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:50:53.702556Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:51:53.763595Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:52:53.800259Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:53:53.861148Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:54:53.901805Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:55:53.962701Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:56:53.989801Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:57:53.998190Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:58:54.059601Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T09:59:54.109084Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:00:54.170976Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:01:54.232717Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:02:54.293866Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:03:54.354961Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:04:54.372354Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:05:54.433789Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:06:54.494745Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:07:54.548031Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:08:54.608664Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:09:54.637587Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:10:54.698368Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:11:54.735955Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:12:54.773762Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:13:54.833567Z | Info | Live bytes: 900.86MB Heap size: 2202.01MB +2024-07-21T10:14:54.886468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T10:14:54.893722Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:15:54.901131Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:16:54.962219Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:17:54.969403Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:18:55.030500Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:19:55.092330Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:20:55.153111Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:21:55.200860Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:22:55.208609Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:23:55.268640Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:24:55.284459Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:25:55.310655Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:26:55.353303Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:27:55.414556Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:28:55.435343Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:29:55.496209Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:30:55.556962Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:31:55.586268Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:32:55.647475Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:33:55.708195Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:34:55.768614Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:35:55.828681Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:36:55.879486Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:37:55.940771Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:38:56.002091Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:39:56.062853Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:40:56.124193Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:41:56.185382Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:42:56.190695Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:43:56.251842Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:44:56.269680Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:45:56.323721Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:46:56.370108Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:47:56.380505Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:48:56.442006Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:49:56.503848Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:50:56.565623Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:51:56.574567Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:52:56.635948Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:53:56.691969Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:54:56.710504Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:55:56.729382Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:56:56.790971Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:57:56.798018Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:58:56.859491Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T10:59:56.878017Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:00:56.939625Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:01:57.001072Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:02:57.009007Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:03:57.069813Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:04:57.131008Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:05:57.191738Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:06:57.251773Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:07:57.308272Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:08:57.368781Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:09:57.429792Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:10:57.490524Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:11:57.550515Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:12:57.610481Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:13:57.670663Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:14:57.730472Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:15:57.790563Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:16:57.842551Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:17:57.902508Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:18:57.962475Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:19:57.985162Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:20:58.045500Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:21:58.105953Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:22:58.165691Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:23:58.218474Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:24:58.278486Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:25:58.338513Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:26:58.398928Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:27:58.458734Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:28:58.515760Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:29:18.548075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T11:29:58.553684Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:30:58.613767Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:31:58.673525Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:32:58.702353Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:33:58.762664Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:34:58.823452Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:35:58.861759Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:36:58.922543Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:37:58.935383Z | Info | Live bytes: 909.64MB Heap size: 2202.01MB +2024-07-21T11:38:06.081197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T11:38:58.988862Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:39:59.000087Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:40:59.041772Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:41:59.102799Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:42:59.162730Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:43:59.223461Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:44:59.257948Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:45:59.318452Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:46:59.362887Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:47:59.423957Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:48:59.484788Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:49:59.532201Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:50:59.579581Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:51:59.639502Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:52:59.699630Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:53:59.759668Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:54:59.782512Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:55:59.842900Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:56:59.902569Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:57:59.941202Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T11:59:00.002319Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:00:00.063076Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:01:00.118808Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:02:00.130918Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:03:00.173688Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:04:00.234812Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:05:00.289594Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:06:00.345664Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:07:00.385327Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:08:00.409664Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:09:00.469551Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:10:00.501565Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:11:00.561624Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:12:00.621653Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:13:00.681598Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:14:00.733637Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:15:00.759548Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:16:00.819630Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:17:00.879588Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:18:00.940036Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:19:00.945477Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:20:01.005543Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:21:01.030780Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:22:01.092183Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:23:01.152745Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:24:01.213477Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:25:01.273580Z | Info | Live bytes: 911.84MB Heap size: 2202.01MB +2024-07-21T12:26:01.281429Z | Info | Live bytes: 940.32MB Heap size: 2202.01MB +2024-07-21T12:27:01.331472Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:28:01.348717Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:29:01.409643Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:30:01.470975Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:31:01.481037Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:32:01.542301Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:33:01.603586Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:34:01.665353Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:35:01.723287Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:36:01.784728Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:37:01.794609Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:38:01.797954Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:39:01.852748Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:40:01.914119Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:41:01.965993Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:42:01.979460Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:43:02.031060Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:44:02.091587Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:45:02.152379Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:46:02.213284Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:47:02.273529Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:48:02.333658Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:49:02.394270Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:50:02.454489Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:51:02.515322Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:52:02.520115Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:53:02.576144Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:54:02.637617Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:55:02.685004Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:56:02.746500Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:57:02.807999Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:58:02.813153Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T12:59:02.823204Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:00:02.884591Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:01:02.945727Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:02:03.006674Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:03:03.067477Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:04:03.098069Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:05:03.159512Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:06:03.220851Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:07:03.238731Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:08:03.300227Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:09:03.362080Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:10:03.423208Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:11:03.484492Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:12:03.509938Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:13:03.571901Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:14:03.597985Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:15:03.630044Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:16:03.674171Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:17:03.735458Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:18:03.797008Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:19:03.858643Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:20:03.920085Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:21:03.981590Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:22:04.043175Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:23:04.104329Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:24:04.165174Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:25:04.226806Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:26:04.288636Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:27:04.349979Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:28:04.411258Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:29:04.472737Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:30:04.534019Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:31:04.589891Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:32:04.646143Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:33:04.707140Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:34:04.747850Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:35:04.783763Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:36:04.844515Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:37:04.896790Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:38:04.901886Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:39:04.963231Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:40:05.024597Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:41:05.085925Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:42:05.133820Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:43:05.195062Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:44:05.197921Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:45:05.259113Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:46:05.320201Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:47:05.381269Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:48:05.442284Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:49:05.449790Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:50:05.453851Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:51:05.461650Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:52:05.523098Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:53:05.566000Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:54:05.627447Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:55:05.688872Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:56:05.750002Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:57:05.805921Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:58:05.861510Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T13:59:05.922847Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:00:05.939642Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:01:05.949972Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:02:05.966001Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:03:05.999380Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:04:06.013983Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:05:06.075230Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:06:06.136597Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:07:06.157938Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:08:06.219259Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:09:06.253869Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:10:06.268916Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:11:06.329791Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:12:06.367580Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:13:06.381904Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:14:06.417976Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:15:06.437941Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:16:06.499261Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:17:06.560545Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:18:06.621816Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:19:06.683065Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:20:06.744158Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:21:06.748680Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:22:06.809958Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:23:06.871231Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:24:06.885885Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:25:06.908980Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:26:06.949847Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:27:06.994976Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:28:07.014339Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:29:07.024756Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:30:07.086194Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:31:07.133711Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:32:07.195060Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:33:07.213846Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:34:07.253722Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:35:07.310208Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:36:07.371591Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:37:07.432766Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:38:07.437854Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:39:07.463035Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:40:07.524545Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:41:07.557643Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:42:07.619092Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:43:07.634183Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:44:07.695588Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:45:07.756913Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:46:07.805993Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:47:07.838363Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:48:07.898844Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:49:07.960217Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:50:08.021681Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:51:08.083050Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:52:08.113248Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:53:08.174792Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:54:08.236115Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:55:08.297251Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:56:08.358622Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:57:08.420095Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:58:08.481455Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T14:59:08.542763Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:00:08.574491Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:01:08.635872Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:02:08.697583Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:03:08.759104Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:04:08.820664Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:05:08.882021Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:06:08.943546Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:07:09.005110Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:08:09.066716Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:09:09.128061Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:10:09.189556Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:11:09.251128Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:12:09.272617Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:13:09.304748Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:14:09.359734Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:15:09.382738Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:16:09.444257Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:17:09.505594Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:18:09.566882Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:19:09.616157Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:20:09.623256Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:21:09.672534Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:22:09.700576Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:23:09.761791Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:24:09.822658Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:25:09.882823Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:26:09.933825Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:27:09.994929Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:28:10.056246Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:29:10.093903Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:30:10.125820Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:31:10.187034Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:32:10.248266Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:33:10.309934Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:34:10.371024Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:35:10.432314Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:36:10.494090Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:37:10.555890Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:38:10.573890Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:39:10.635342Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:40:10.697086Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:41:10.705787Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:42:10.708701Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:43:10.761815Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:44:10.765835Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:45:10.810830Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:46:10.872104Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:47:10.933270Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:48:10.994583Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:49:11.055926Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:50:11.098908Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:51:11.149833Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:52:11.211100Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:53:11.219185Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:54:11.279504Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:55:11.340730Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:56:11.402007Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:57:11.421906Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:58:11.483177Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T15:59:11.544331Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:00:11.589888Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:01:11.611993Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:02:11.673554Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:03:11.720633Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:04:11.740531Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:05:11.767543Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:06:11.828811Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:07:11.849815Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:08:11.911016Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:09:11.972382Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:10:12.033786Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:11:12.095002Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:12:12.156193Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:13:12.217773Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:14:12.236487Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:15:12.253621Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:16:12.313535Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:17:12.326803Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:18:12.386965Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:19:12.407929Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:20:12.410997Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:21:12.449533Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:22:12.510345Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:23:12.561720Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:24:12.574221Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:25:12.581919Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:26:12.642736Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:27:12.703838Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:28:12.763631Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:29:12.764840Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:30:12.825956Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:31:12.887027Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:32:12.894978Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:33:12.913768Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:34:12.954256Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:35:12.959899Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:36:13.020710Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:37:13.080819Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:38:13.106890Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:39:13.167884Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:40:13.209490Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:41:13.270734Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:42:13.325937Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:43:13.349897Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:44:13.410727Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:45:13.471528Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:46:13.531601Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:47:13.591703Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:48:13.652547Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:49:13.712583Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:50:13.772492Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:51:13.792654Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:52:13.853743Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:53:13.913683Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:54:13.973698Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:55:13.996480Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:56:14.014272Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:57:14.029866Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:58:14.090611Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T16:59:14.150756Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:00:14.180827Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:01:14.241634Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:02:14.301570Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:03:14.356435Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:04:14.394683Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:05:14.454562Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:06:14.478592Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:07:14.499367Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:08:14.532249Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:09:14.592900Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:10:14.652628Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:11:14.669426Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:12:14.680603Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:13:14.740613Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:14:14.786705Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:15:14.847485Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:16:14.907621Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:17:14.968839Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:18:15.030242Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:19:15.091511Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:20:15.151619Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:21:15.173702Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:22:15.234526Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:23:15.239770Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:24:15.300644Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:25:15.360724Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:26:15.379050Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:27:15.439737Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:28:15.500513Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:29:15.561291Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:30:15.617920Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:31:15.678971Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:32:15.688319Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:33:15.748730Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:34:15.809572Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:35:15.865666Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:36:15.925591Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:37:15.928083Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:38:15.988937Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:39:16.049677Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:40:16.110642Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:41:16.170695Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:42:16.231578Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:43:16.285086Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:44:16.346083Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:45:16.407074Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:46:16.458603Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:47:16.518782Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:48:16.579688Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:49:16.639691Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:50:16.700534Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:51:16.760666Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:52:16.780592Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:53:16.840651Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:54:16.901460Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:55:16.961672Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:56:17.022317Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:57:17.048838Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:58:17.109658Z | Info | Live bytes: 940.79MB Heap size: 2202.01MB +2024-07-21T17:59:16.944999Z | Error | Got EOF +2024-07-21 19:31:06.8970000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-21 19:31:06.8990000 [client] INFO Finding haskell-language-server +2024-07-21 19:31:06.9000000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:06.9010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:06.9170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-21 19:31:07.2700000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:07.2700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:07.2800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-21 19:31:07.7820000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:07.7830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:07.8060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-21 19:31:08.0670000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:08.0670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:08.0780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-21 19:31:08.3630000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:08.3640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:08.3790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-21 19:31:08.4020000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:08.4030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:08.4120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-21 19:31:08.4420000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:08.4420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:08.4600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-21 19:31:08.5070000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-21 19:31:08.5910000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:08.5920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:08.6020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-21 19:31:08.9640000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-21 19:31:08.9660000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-21 19:31:22.1940000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-21 19:31:22.3100000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-21 19:31:22.3100000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:22.3100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:22.3160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-21 19:31:22.4410000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:22.4410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:22.4470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-21 19:31:22.4650000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:22.4650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:22.4700000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-21 19:31:22.4870000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:22.4870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:22.4960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-21 19:31:22.5120000 [client] INFO Checking for ghcup installation +2024-07-21 19:31:22.5120000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:31:22.5170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-21 19:31:22.6540000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-21 19:31:22.6550000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-21 19:31:22.6550000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-21 19:31:22.6550000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-21 19:31:22.6550000 [client] INFO server environment variables: +2024-07-21 19:31:22.6550000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-21 19:31:22.6550000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-21 19:31:22.6550000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-21 19:31:22.6580000 [client] INFO Starting language server +2024-07-21T19:31:34.322093Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-21T19:31:34.322903Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-21T19:31:34.323125Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-21T19:31:34.329561Z | Info | Logging heap statistics every 60.00s +2024-07-21T19:31:34.345772Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-21T19:31:34.346466Z | Info | Starting server +2024-07-21T19:31:34.351166Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-21T19:31:34.466010Z | Info | Started LSP server in 0.12s +2024-07-21T19:31:36.151267Z | Info | LSP: received shutdown +2024-07-21T19:31:36.152538Z | Info | Reactor thread stopped +2024-07-21T19:31:36.161926Z | Error | Got EOF +2024-07-21 19:50:48.0120000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-21 19:50:48.0150000 [client] INFO Finding haskell-language-server +2024-07-21 19:50:48.0170000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:48.0180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:48.0340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-21 19:50:48.2250000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:48.2250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:48.2320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-21 19:50:48.4490000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:48.4490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:48.4560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-21 19:50:48.6690000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:48.6690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:48.6790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-21 19:50:48.9510000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:48.9510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:48.9610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-21 19:50:48.9830000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:48.9830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:48.9940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-21 19:50:49.0150000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:49.0150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:49.0230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-21 19:50:49.0520000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-21 19:50:49.2030000 [client] INFO Checking for ghcup installation +2024-07-21 19:50:49.2030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:50:49.2140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-21 19:50:49.3820000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-21 19:50:49.3830000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-21 19:51:03.0380000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-21 19:51:03.1660000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-21 19:51:03.1670000 [client] INFO Checking for ghcup installation +2024-07-21 19:51:03.1670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:51:03.1710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-21 19:51:03.2760000 [client] INFO Checking for ghcup installation +2024-07-21 19:51:03.2770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:51:03.2820000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-21 19:51:03.3020000 [client] INFO Checking for ghcup installation +2024-07-21 19:51:03.3020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:51:03.3080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-21 19:51:03.3230000 [client] INFO Checking for ghcup installation +2024-07-21 19:51:03.3230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:51:03.3290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-21 19:51:03.3430000 [client] INFO Checking for ghcup installation +2024-07-21 19:51:03.3430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-21 19:51:03.3490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-21 19:51:03.4650000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-21 19:51:03.4650000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-21 19:51:03.4650000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-21 19:51:03.4650000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-21 19:51:03.4660000 [client] INFO server environment variables: +2024-07-21 19:51:03.4660000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-21 19:51:03.4660000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-21 19:51:03.4660000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-21 19:51:03.4670000 [client] INFO Starting language server +2024-07-21T19:51:16.599963Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-21T19:51:16.601239Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-21T19:51:16.601611Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-21T19:51:16.605255Z | Info | Logging heap statistics every 60.00s +2024-07-21T19:51:16.615335Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-21T19:51:16.616042Z | Info | Starting server +2024-07-21T19:51:16.617616Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-21T19:51:16.673954Z | Info | Started LSP server in 0.06s +2024-07-21T19:51:18.443404Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-21T19:51:18.444101Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-21T19:51:19.005190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T19:51:19.005411Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T19:51:20.363285Z | Info | Load cabal cradle using single file +2024-07-21T19:51:21.482843Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT36665-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-21T19:51:25.822681Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-21T19:51:25.832173Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-21T19:51:51.131289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T19:52:16.625702Z | Info | Live bytes: 433.08MB Heap size: 1966.08MB +2024-07-21T19:53:16.686233Z | Info | Live bytes: 433.08MB Heap size: 1966.08MB +2024-07-21T19:54:13.173454Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T19:54:16.690903Z | Info | Live bytes: 439.56MB Heap size: 1966.08MB +2024-07-21T19:55:16.741642Z | Info | Live bytes: 439.56MB Heap size: 1966.08MB +2024-07-21T19:56:16.802396Z | Info | Live bytes: 439.56MB Heap size: 1966.08MB +2024-07-21T19:57:16.863006Z | Info | Live bytes: 439.56MB Heap size: 1966.08MB +2024-07-21T19:58:16.869782Z | Info | Live bytes: 439.56MB Heap size: 1966.08MB +2024-07-21T19:59:16.930457Z | Info | Live bytes: 439.56MB Heap size: 1966.08MB +2024-07-21T20:00:16.990844Z | Info | Live bytes: 439.56MB Heap size: 1966.08MB +2024-07-21T20:01:11.864391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T20:01:16.993632Z | Info | Live bytes: 462.02MB Heap size: 1966.08MB +2024-07-21T20:01:42.295571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T20:01:59.515596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T20:02:17.008812Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:03:17.068855Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:04:17.124540Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:05:17.184712Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:06:17.244734Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:07:17.304757Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:08:17.365437Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:09:17.425937Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:10:17.445221Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:11:17.505596Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:12:17.565972Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:13:17.599753Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:14:17.606194Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:15:17.624141Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:16:17.683731Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:17:17.715904Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:18:17.775644Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:19:17.835880Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:20:17.895701Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:21:17.955772Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:22:18.016358Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:23:18.076809Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:24:18.137377Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:25:18.139394Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:26:18.199733Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:27:18.260320Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:28:18.312691Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:29:18.372649Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:30:18.432827Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:31:18.492681Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:32:18.535892Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:33:18.539586Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:34:18.599648Z | Info | Live bytes: 504.33MB Heap size: 1966.08MB +2024-07-21T20:34:41.926179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T20:35:18.627624Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:36:18.688035Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:37:18.748529Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:38:18.809039Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:39:18.868732Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:40:18.915923Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:41:18.976509Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:42:19.037447Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:43:19.044449Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:44:19.105153Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:45:19.165891Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:46:19.226637Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:47:19.287306Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:48:19.347841Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:49:19.359952Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:50:19.420634Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:51:19.446095Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:52:19.479522Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:53:19.537721Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:54:19.567198Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:55:19.568083Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:56:19.628678Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:57:19.689340Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:58:19.750011Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T20:59:19.810722Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:00:19.871438Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:01:19.888659Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:02:19.895943Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:03:19.956522Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:04:20.017117Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:05:20.077894Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:06:20.095931Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:07:20.156670Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:08:20.217263Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:09:20.277796Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:10:20.338435Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:11:20.399103Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:12:20.459765Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:13:20.520340Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:14:20.580911Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:15:20.609594Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:16:20.650691Z | Info | Live bytes: 517.78MB Heap size: 1966.08MB +2024-07-21T21:16:54.967125Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-21T21:17:20.661384Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:18:20.686733Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:19:20.741794Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:20:20.748005Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:21:20.784504Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:22:20.844799Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:23:20.876678Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:24:20.936913Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:25:20.996644Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:26:21.057228Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:27:21.116839Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:28:21.176644Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:29:21.194701Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:30:21.234962Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:31:21.269776Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:32:21.330458Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:33:21.343843Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:34:21.404535Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:35:21.465266Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:36:21.481663Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:37:21.542350Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:38:21.602776Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:39:21.663505Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:40:21.719198Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:41:21.778766Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:42:21.785265Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:43:21.792055Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:44:21.841270Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:45:21.900922Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:46:21.960857Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:47:22.020846Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:48:22.068488Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:49:22.129230Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:50:22.189908Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:51:22.231792Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:52:22.292238Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:53:22.296837Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:54:22.357349Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:55:22.417850Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:56:22.478359Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:57:22.490385Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:58:22.515005Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T21:59:22.575508Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T22:00:22.635979Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T22:01:22.696508Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T22:02:22.756988Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T22:03:22.817472Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T22:04:22.877913Z | Info | Live bytes: 546.70MB Heap size: 1966.08MB +2024-07-21T22:04:45.979240Z | Error | Got EOF +2024-07-22 07:36:02.1790000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-22 07:36:02.1820000 [client] INFO Finding haskell-language-server +2024-07-22 07:36:02.1850000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:02.1850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:02.1950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-22 07:36:02.4340000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:02.4340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:02.4410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-22 07:36:02.7280000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:02.7280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:02.7380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-22 07:36:03.0050000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:03.0050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:03.0110000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-22 07:36:03.2090000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:03.2090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:03.2150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-22 07:36:03.2410000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:03.2410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:03.2490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-22 07:36:03.2990000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:03.2990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:03.3050000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-22 07:36:03.3260000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-22 07:36:03.4220000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:03.4220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:03.4290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-22 07:36:03.6670000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-22 07:36:03.6670000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-22 07:36:12.3660000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-22 07:36:12.4900000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-22 07:36:12.4900000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:12.4910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:12.4950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-22 07:36:12.5800000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:12.5800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:12.5850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-22 07:36:12.6050000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:12.6050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:12.6100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-22 07:36:12.6250000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:12.6250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:12.6300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-22 07:36:12.6440000 [client] INFO Checking for ghcup installation +2024-07-22 07:36:12.6440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 07:36:12.6480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-22 07:36:12.7430000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-22 07:36:12.7440000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-22 07:36:12.7440000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-22 07:36:12.7440000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-22 07:36:12.7440000 [client] INFO server environment variables: +2024-07-22 07:36:12.7440000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-22 07:36:12.7440000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-22 07:36:12.7440000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-22 07:36:12.7460000 [client] INFO Starting language server +2024-07-22T07:36:23.335336Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-22T07:36:23.337140Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-22T07:36:23.337319Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T07:36:23.339851Z | Info | Logging heap statistics every 60.00s +2024-07-22T07:36:23.348299Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T07:36:23.348782Z | Info | Starting server +2024-07-22T07:36:23.365781Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-22T07:36:23.438280Z | Info | Started LSP server in 0.09s +2024-07-22T07:36:24.979144Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-07-22T07:36:24.980366Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T07:36:25.542712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T07:36:25.543183Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T07:36:26.718110Z | Info | Load cabal cradle using single file +2024-07-22T07:36:27.922579Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT14614-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T07:36:32.373509Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-22T07:36:32.379649Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-22T07:37:23.388747Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:38:23.449492Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:39:23.509663Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:40:23.563797Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:41:23.623828Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:42:23.684753Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:43:23.744759Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:44:23.804539Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:45:23.862547Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:46:23.923376Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:47:23.954923Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:48:23.969601Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:49:24.029675Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:50:24.041798Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:51:24.101241Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:52:24.140157Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:53:24.167983Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:54:24.229042Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:55:24.289797Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:56:24.350855Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:57:24.411955Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:58:24.472898Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T07:59:24.532337Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T08:00:24.584930Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T08:01:24.646345Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T08:02:24.689405Z | Info | Live bytes: 359.90MB Heap size: 1712.32MB +2024-07-22T08:03:24.690445Z | Info | Live bytes: 393.79MB Heap size: 1712.32MB +2024-07-22T08:04:24.720234Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:05:24.780968Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:06:24.842289Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:07:24.903611Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:08:24.954978Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:09:25.016285Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:10:25.029805Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:11:25.091032Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:12:25.151965Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:13:25.212706Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:14:25.273822Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:15:25.334859Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:16:25.395754Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:17:25.402778Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:18:25.463831Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:19:25.524924Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:20:25.586214Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:21:25.647563Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:22:25.708879Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:23:25.770153Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:24:25.831157Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:25:25.849876Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:26:25.910741Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:27:25.971408Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:28:26.032341Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:29:26.092515Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:30:26.152969Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:31:26.213873Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:32:26.274712Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:33:26.330750Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:34:26.377517Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:35:26.438099Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:36:26.498598Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:37:26.555995Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:38:26.615720Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:39:26.668812Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:40:26.728609Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:41:26.745614Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:42:26.746735Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:43:26.767396Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:44:26.810887Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:45:26.851515Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:46:26.897778Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:47:26.959296Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:48:26.989840Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:49:27.034905Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:50:27.065570Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:51:27.126963Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:52:27.187121Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:53:27.248526Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:54:27.258911Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:55:27.290994Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:56:27.352245Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:57:27.397814Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:58:27.458846Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T08:59:27.519800Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:00:27.579660Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:01:27.640664Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:02:27.701741Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:03:27.712234Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:04:27.747311Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:05:27.808539Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:06:27.835012Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:07:27.866872Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:08:27.900146Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:09:27.916693Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:10:27.939569Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:11:27.995065Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:12:28.056334Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:13:28.117327Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:14:28.178651Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:15:28.203927Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:16:28.216263Z | Info | Live bytes: 546.99MB Heap size: 2171.60MB +2024-07-22T09:17:10.567730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:17:12.324654Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:17:16.454470Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-22T09:17:28.227556Z | Info | Live bytes: 740.03MB Heap size: 2171.60MB +2024-07-22T09:17:43.882937Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Script.hs +2024-07-22T09:17:43.883588Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T09:17:43.968409Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:17:44.481468Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:17:45.854393Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:18:01.721516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:18:07.136479Z | Info | Load cabal cradle using single file +2024-07-22T09:18:08.207218Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT14614-178 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T09:18:08.267346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:18:16.455036Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-22T09:18:16.455355Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-22T09:18:16.460148Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-22T09:18:28.239370Z | Info | Live bytes: 813.14MB Heap size: 2841.64MB +2024-07-22T09:19:28.240521Z | Info | Live bytes: 813.14MB Heap size: 2841.64MB +2024-07-22T09:20:00.736545Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:20:02.658379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:20:28.267248Z | Info | Live bytes: 894.05MB Heap size: 2841.64MB +2024-07-22T09:20:36.297423Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:20:38.175745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:20:38.583738Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:20:39.272154Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:20:39.475007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:20:41.419373Z | Info | LSP: received shutdown +2024-07-22T09:20:41.422879Z | Info | Reactor thread stopped +2024-07-22T09:20:41.422900Z | Error | Got EOF +2024-07-22T09:20:46.906588Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-22T09:20:46.907517Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-22T09:20:46.907769Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T09:20:46.910309Z | Info | Logging heap statistics every 60.00s +2024-07-22T09:20:46.918213Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T09:20:46.918992Z | Info | Starting server +2024-07-22T09:20:46.920703Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-22T09:20:46.989823Z | Info | Started LSP server in 0.07s +2024-07-22T09:20:48.306987Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-22T09:20:48.308059Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T09:20:48.851399Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:20:48.851439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:20:49.804785Z | Info | Load cabal cradle using single file +2024-07-22T09:20:50.776640Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT87631-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T09:20:54.293804Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-22T09:20:54.298425Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-22T09:21:46.962934Z | Info | Live bytes: 359.65MB Heap size: 1580.20MB +2024-07-22T09:22:41.909719Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:22:42.484470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:22:42.542490Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-22T09:22:46.967693Z | Info | Live bytes: 444.58MB Heap size: 1879.05MB +2024-07-22T09:23:02.787507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:20.307789Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Script.hs +2024-07-22T09:23:20.308299Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T09:23:20.357891Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:21.883796Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:24.596562Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:25.831734Z | Info | Load cabal cradle using single file +2024-07-22T09:23:26.876799Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT87631-15 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T09:23:28.999728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:29.441072Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-22T09:23:30.228293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:30.651831Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-22T09:23:30.652218Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-22T09:23:30.659068Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-22T09:23:31.701676Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-22T09:23:32.080369Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:44.192308Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:45.120594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:45.722219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:46.325225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:46.970018Z | Info | Live bytes: 791.97MB Heap size: 2501.90MB +2024-07-22T09:23:58.268365Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:23:58.569189Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:59.163556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:23:59.355141Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:24:00.072428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:24:47.018729Z | Info | Live bytes: 841.12MB Heap size: 2501.90MB +2024-07-22T09:24:49.775201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:24:51.133732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:24:51.817085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:24:52.639953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:24:53.885311Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-22T09:25:09.407514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:10.297854Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:25:39.097922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:40.175879Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:25:40.338212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:41.088760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:41.285034Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:25:41.405917Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:25:41.795565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:43.307888Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:43.900264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:45.337270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:47.022189Z | Info | Live bytes: 890.11MB Heap size: 2501.90MB +2024-07-22T09:25:48.212945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:57.594121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:58.358314Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:25:59.018809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:26:02.840386Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:26:02.935584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:26:03.575803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:26:04.263893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:26:30.592520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:26:47.047020Z | Info | Live bytes: 933.73MB Heap size: 2501.90MB +2024-07-22T09:27:38.365302Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:27:47.056795Z | Info | Live bytes: 943.84MB Heap size: 2501.90MB +2024-07-22T09:28:47.118192Z | Info | Live bytes: 943.84MB Heap size: 2501.90MB +2024-07-22T09:29:06.069919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:29:10.365419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:29:39.921161Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:29:41.774524Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:29:47.122219Z | Info | Live bytes: 949.13MB Heap size: 2501.90MB +2024-07-22T09:30:47.182791Z | Info | Live bytes: 949.13MB Heap size: 2501.90MB +2024-07-22T09:30:59.459848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:00.121455Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:03.049011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:26.851577Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:29.403002Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:29.785222Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ ] +2024-07-22T09:31:35.100507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:36.529600Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:36.634680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:36.778382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:36.925138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:37.044243Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:37.495247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:37.566334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:38.020388Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:38.070583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:38.241893Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:38.778250Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:39.047988Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:39.247378Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:31:40.081321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:42.008300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:42.791062Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:42.960051Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-22T09:31:43.672100Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:31:47.188246Z | Info | Live bytes: 948.39MB Heap size: 2501.90MB +2024-07-22T09:31:55.205683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:04.789606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:21.104352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:22.772170Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:23.748415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:23.961269Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:32:24.453613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:24.584677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:32:28.020595Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:28.893195Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:32:29.385373Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:33.613854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:34.210816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:40.897781Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-22T09:32:45.074175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:32:47.192333Z | Info | Live bytes: 959.66MB Heap size: 2501.90MB +2024-07-22T09:32:59.924621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:33:01.530726Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-22T09:33:12.735230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:33:13.986199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:33:14.479893Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-22T09:33:47.225963Z | Info | Live bytes: 974.62MB Heap size: 2501.90MB +2024-07-22T09:34:47.266929Z | Info | Live bytes: 974.62MB Heap size: 2501.90MB +2024-07-22T09:35:10.534049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:18.581923Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:35:19.057313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:25.946197Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:35:26.439600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:30.321221Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-22T09:35:31.295663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:41.530629Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:35:42.024141Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:43.604778Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-22T09:35:44.743270Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:45.477138Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:35:47.268771Z | Info | Live bytes: 987.07MB Heap size: 2501.90MB +2024-07-22T09:35:52.111190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:56.916168Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:58.237921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:35:58.797145Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-22T09:36:00.513904Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:36:41.500993Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:41.606733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:41.767537Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:41.927893Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:41.965578Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:36:42.130129Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:42.566847Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:42.587339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:36:43.055107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:43.217560Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:43.352472Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:43.481457Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:43.552245Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:36:43.589186Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:43.679033Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:36:44.177277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:36:47.272566Z | Info | Live bytes: 1023.74MB Heap size: 2501.90MB +2024-07-22T09:37:47.332009Z | Info | Live bytes: 1023.74MB Heap size: 2501.90MB +2024-07-22T09:37:52.685136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:37:53.016685Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:37:55.339269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:37:56.560636Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:37:58.616302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:04.168178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:04.725146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:05.328305Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:05.960025Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:06.999152Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:38:18.893639Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:19.425731Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:38:19.544344Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:38:19.669183Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:38:20.471652Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:38:21.538495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:22.339550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:23.024671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:24.554326Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:26.835092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:27.517950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:31.255718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:32.724867Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:38:47.347329Z | Info | Live bytes: 1076.41MB Heap size: 2501.90MB +2024-07-22T09:38:57.632947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:38:58.622346Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:39:25.389329Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:39:28.285377Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-07-22T09:39:29.222622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:39:33.647045Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:39:37.958341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:39:38.988408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:39:39.599130Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Script.hs" ] +2024-07-22T09:39:47.356594Z | Info | Live bytes: 1089.45MB Heap size: 2501.90MB +2024-07-22T09:40:26.049936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:30.649977Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:47.370463Z | Info | Live bytes: 1092.08MB Heap size: 2501.90MB +2024-07-22T09:40:50.669248Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:50.987080Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:51.119830Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:51.148068Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:51.255035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:51.444569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:51.757426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:51.896927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:52.003274Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:52.359747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:52.442992Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:52.653677Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:52.788817Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:52.879899Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:52.916882Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:52.931793Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:53.042787Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:53.539202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:53.829233Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:40:54.312516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:55.699933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:56.553941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:40:57.226960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:12.171331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:13.027501Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:13.739525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:14.494331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:29.744500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:32.519736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:32.806255Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:41:37.096989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:37.692072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:38.809034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:39.810363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:41.362814Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:41:41.516626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:42.071953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:46.862367Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:41:47.288136Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:47.371222Z | Info | Live bytes: 1249.45MB Heap size: 2615.15MB +2024-07-22T09:41:47.851405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:51.327397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:53.610790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:56.747506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:41:58.124563Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:41:58.717596Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:42:27.815519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:42:32.495827Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T09:42:47.386681Z | Info | Live bytes: 1273.80MB Heap size: 2662.33MB +2024-07-22T09:43:18.425692Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:18.540016Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:18.672160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:18.734131Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:18.754458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:43:18.864749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:18.956873Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:19.371841Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:43:19.927487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:43:22.185023Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:22.345585Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:22.605439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:22.674728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:43:24.215005Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:24.361633Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:24.438463Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:24.566296Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:24.718191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:43:24.869125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:25.373191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:43:26.008954Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T09:43:26.375940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T09:43:47.397985Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:44:47.459840Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:45:47.521738Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:46:47.546953Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:47:47.608557Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:48:47.610969Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:49:47.642983Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:50:47.674969Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:51:47.697356Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:52:47.745145Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:53:47.749237Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:54:47.810575Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:55:47.834889Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:56:47.895945Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:57:47.956974Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:58:47.968100Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T09:59:48.029268Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:00:48.090591Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:01:48.151752Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:02:48.207074Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:03:48.267813Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:04:48.283626Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:05:48.314939Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:06:48.339920Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:07:48.354823Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:08:48.401398Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:09:48.426511Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:10:48.488222Z | Info | Live bytes: 1306.86MB Heap size: 2711.62MB +2024-07-22T10:11:30.066551Z | Info | LSP: received shutdown +2024-07-22T10:11:30.068363Z | Error | Got EOF +2024-07-22 11:03:06.9430000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-22 11:03:06.9440000 [client] INFO Finding haskell-language-server +2024-07-22 11:03:06.9440000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:06.9440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:06.9500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-22 11:03:07.3750000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:07.3750000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:07.3800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-22 11:03:07.4970000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:07.4980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:07.5030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-22 11:03:07.6090000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:07.6090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:07.6160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-22 11:03:07.7270000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:07.7270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:07.7330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-22 11:03:07.7470000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:07.7470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:07.7530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-22 11:03:07.7680000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:07.7680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:07.7740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-22 11:03:07.7940000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-22 11:03:07.8380000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:07.8380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:07.8440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-22 11:03:07.9610000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-22 11:03:07.9610000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-22 11:03:10.5770000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-22 11:03:10.8390000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-22 11:03:10.8390000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:10.8390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:10.8470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-22 11:03:10.9230000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:10.9230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:10.9270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-22 11:03:10.9420000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:10.9420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:10.9470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-22 11:03:10.9610000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:10.9610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:10.9680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-22 11:03:10.9830000 [client] INFO Checking for ghcup installation +2024-07-22 11:03:10.9840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-22 11:03:10.9910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-22 11:03:11.0770000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-22 11:03:11.0770000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-22 11:03:11.0770000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-22 11:03:11.0770000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-22 11:03:11.0770000 [client] INFO server environment variables: +2024-07-22 11:03:11.0770000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-22 11:03:11.0770000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-22 11:03:11.0780000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-22 11:03:11.0790000 [client] INFO Starting language server +2024-07-22T11:03:19.951601Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-22T11:03:19.952679Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-22T11:03:19.952896Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T11:03:19.955531Z | Info | Logging heap statistics every 60.00s +2024-07-22T11:03:19.962551Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T11:03:19.962927Z | Info | Starting server +2024-07-22T11:03:19.964871Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-22T11:03:20.004302Z | Info | Started LSP server in 0.04s +2024-07-22T11:03:21.275791Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Tx.hs +2024-07-22T11:03:21.276853Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T11:03:21.688683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:03:22.719038Z | Info | Load cabal cradle using single file +2024-07-22T11:03:23.686191Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT114885-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T11:03:45.575629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:03:46.038026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:03:52.153848Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-ba9215ff2fde0ea115d58976f5fb0c7fb35cc9cc +2024-07-22T11:03:52.157862Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-22T11:03:54.813990Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Eras/Case.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-22T11:04:00.982150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:04:07.117679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:04:15.986470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:04:19.959606Z | Info | Live bytes: 607.01MB Heap size: 1943.01MB +2024-07-22T11:04:20.645919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:05:19.962421Z | Info | Live bytes: 618.69MB Heap size: 1943.01MB +2024-07-22T11:05:22.010939Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Eras.hs +2024-07-22T11:05:22.011721Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T11:05:22.077160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:05:23.541614Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:05:24.665585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:05:29.726301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:05:44.231763Z | Info | Load cabal cradle using single file +2024-07-22T11:05:45.247037Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT114885-84 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T11:05:53.214634Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-4680c848285cdcb20b8c192b1586026351591b55 +2024-07-22T11:05:53.215005Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-4680c848285cdcb20b8c192b1586026351591b55 +2024-07-22T11:05:53.222148Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-22T11:06:19.979721Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:07:19.990365Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:08:20.051273Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:09:20.084664Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:10:20.145216Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:11:20.153177Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:12:20.213951Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:13:20.233525Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:14:20.254455Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:15:20.304281Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:16:20.336393Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:17:20.357497Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:18:20.371767Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:19:20.379609Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:20:20.441065Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:21:20.502469Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:22:20.563392Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:23:20.580319Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:24:20.640880Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:24:24.477761Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:25:20.701878Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:26:20.707698Z | Info | Live bytes: 1094.13MB Heap size: 2760.90MB +2024-07-22T11:27:16.399132Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:20.713848Z | Info | Live bytes: 1106.12MB Heap size: 2760.90MB +2024-07-22T11:27:27.062301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:32.498293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:36.612869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:47.251539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:48.085700Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:49.071571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:49.244251Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:27:49.547607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:50.415291Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:50.921750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:51.365530Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:51.873279Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:52.394182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:52.825248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:53.319656Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:55.873303Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:56.191321Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:27:56.338364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:56.383766Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:27:56.760034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:57.233870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:57.776043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:58.370285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:58.914310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:59.585721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:27:59.729409Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:27:59.876853Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:00.000072Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:00.073284Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:00.092934Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:00.155177Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:00.198112Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:00.521462Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:03.865193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:04.816587Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:04.993035Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:05.096709Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:05.175185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:05.208548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:05.294181Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:05.374116Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:05.493671Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:05.664886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:05.834196Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:05.992132Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:06.090107Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:06.201988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:08.534899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:10.336500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:10.932549Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:11.035832Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.122086Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.182697Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.254442Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.326099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.402689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:11.455522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.525718Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.606727Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.733521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:11.825236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:12.451811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:16.849239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:17.572444Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T11:28:18.036292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:19.943634Z | Info | LSP: received shutdown +2024-07-22T11:28:19.946378Z | Info | Reactor thread stopped +2024-07-22T11:28:19.946633Z | Error | Got EOF +2024-07-22T11:28:25.236514Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-22T11:28:25.237288Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-22T11:28:25.237633Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T11:28:25.240248Z | Info | Logging heap statistics every 60.00s +2024-07-22T11:28:25.246779Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-22T11:28:25.247203Z | Info | Starting server +2024-07-22T11:28:25.249118Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-22T11:28:25.287835Z | Info | Started LSP server in 0.04s +2024-07-22T11:28:26.487465Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Tx.hs +2024-07-22T11:28:26.488552Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T11:28:26.920230Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:27.986428Z | Info | Load cabal cradle using single file +2024-07-22T11:28:28.978709Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT135003-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T11:28:36.585158Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-2d0a2cc7c1364f1818ff61ed788661ca3c1509d4 +2024-07-22T11:28:36.589688Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-22T11:28:50.060586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:50.279866Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:50.580178Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:50.645213Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:50.795481Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:50.997772Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:28:51.187434Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:28:51.548591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:29:25.255659Z | Info | Live bytes: 557.48MB Heap size: 1904.21MB +2024-07-22T11:30:05.974553Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:09.783518Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:11.777301Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:12.978110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:15.238442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:15.422563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:30:15.543325Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:30:15.650239Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:30:15.781786Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:30:15.795496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:15.845584Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:30:15.998681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:30:16.220047Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:16.724048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:17.235883Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:17.973288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:18.475811Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:18.941663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:23.961760Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:25.258439Z | Info | Live bytes: 593.97MB Heap size: 2276.46MB +2024-07-22T11:30:26.516380Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:26.957527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:32.856155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:30:33.145375Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T11:31:25.308419Z | Info | Live bytes: 607.02MB Heap size: 2276.46MB +2024-07-22T11:32:25.349124Z | Info | Live bytes: 607.02MB Heap size: 2276.46MB +2024-07-22T11:32:33.381487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:32:35.251139Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:32:40.240246Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:32:40.650296Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T11:33:19.181856Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:33:25.394243Z | Info | Live bytes: 720.57MB Heap size: 2276.46MB +2024-07-22T11:34:05.081571Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:34:25.425456Z | Info | Live bytes: 720.57MB Heap size: 2276.46MB +2024-07-22T11:34:37.857006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:34:38.343960Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T11:34:46.761773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:35:06.627191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:35:25.474039Z | Info | Live bytes: 713.77MB Heap size: 2276.46MB +2024-07-22T11:36:13.512812Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:36:13.769468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:36:13.870570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:14.284505Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:14.468476Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:36:14.834033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:21.209318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:23.148160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:24.370193Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:25.227744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:25.475790Z | Info | Live bytes: 756.07MB Heap size: 2276.46MB +2024-07-22T11:36:25.706241Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:29.466155Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:36:31.392813Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T11:37:25.530762Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:38:25.591529Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:39:25.643298Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:40:25.705238Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:41:25.766771Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:42:25.828254Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:43:25.843659Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:44:25.905306Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:45:18.106770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:45:25.907621Z | Info | Live bytes: 745.85MB Heap size: 2276.46MB +2024-07-22T11:45:32.260360Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:46:10.375039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:46:25.920974Z | Info | Live bytes: 960.74MB Heap size: 2276.46MB +2024-07-22T11:47:25.971700Z | Info | Live bytes: 960.74MB Heap size: 2276.46MB +2024-07-22T11:48:26.024760Z | Info | Live bytes: 960.74MB Heap size: 2276.46MB +2024-07-22T11:49:26.085620Z | Info | Live bytes: 960.74MB Heap size: 2276.46MB +2024-07-22T11:50:26.131745Z | Info | Live bytes: 960.74MB Heap size: 2276.46MB +2024-07-22T11:50:55.412770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:51:26.193248Z | Info | Live bytes: 974.11MB Heap size: 2276.46MB +2024-07-22T11:52:26.254654Z | Info | Live bytes: 974.11MB Heap size: 2276.46MB +2024-07-22T11:53:26.315877Z | Info | Live bytes: 974.11MB Heap size: 2276.46MB +2024-07-22T11:54:26.377717Z | Info | Live bytes: 974.11MB Heap size: 2276.46MB +2024-07-22T11:55:26.420291Z | Info | Live bytes: 974.11MB Heap size: 2276.46MB +2024-07-22T11:56:07.097336Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:56:22.849809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:56:26.451778Z | Info | Live bytes: 974.11MB Heap size: 2276.46MB +2024-07-22T11:56:48.425066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:56:58.462699Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:01.024509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:02.716353Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-22T11:57:05.199112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:26.477552Z | Info | Live bytes: 978.06MB Heap size: 2276.46MB +2024-07-22T11:57:33.082444Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:57:33.442447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:33.802619Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:57:34.000378Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:34.493174Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:34.531025Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:57:34.959634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:41.800954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:49.385398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:49.938332Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:50.509299Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:51.170135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:52.047478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:52.988042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:55.096576Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:57:55.384784Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:57:55.467449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:55.906769Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:57:56.030665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T11:57:56.402950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:58:00.902005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:58:14.010878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T11:58:16.967789Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T11:58:26.488407Z | Info | Live bytes: 1015.95MB Heap size: 2276.46MB +2024-07-22T11:59:26.549503Z | Info | Live bytes: 1015.95MB Heap size: 2276.46MB +2024-07-22T12:00:06.572316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:07.787684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:25.443569Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:25.530981Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:25.699101Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:25.787027Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:25.962264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:26.036960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:26.333319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:26.551418Z | Info | Live bytes: 1030.61MB Heap size: 2276.46MB +2024-07-22T12:00:26.825938Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:26.946496Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:27.096082Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:27.189368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:27.364492Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:27.578986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:27.686756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:27.729447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:27.741302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:28.210527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:28.231920Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:28.449583Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:28.770125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:28.814944Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:28.913289Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:29.067665Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:29.271349Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:29.281206Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:29.651757Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:29.775766Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:29.929838Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:30.008759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:30.021791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:30.391235Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:30.486959Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:30.761871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:31.254750Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:31.917859Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:32.044399Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:32.411830Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:32.545291Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:32.741840Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:32.911020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:32.970117Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:33.337517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:33.611834Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:33.982809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:34.278894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:34.601292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:34.650075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:34.731376Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:34.826850Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:00:35.098525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:35.731536Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:36.702510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:38.121816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:38.695920Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:39.977166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:41.525556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:44.223636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:46.256658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:46.709919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:49.581764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:53.054963Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:00:59.538293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:00.611816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:01:00.741316Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:01:00.831843Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:01:00.925436Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:01:00.992421Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:01.705745Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:01:01.796941Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:10.077945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:11.320897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:11.962242Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:12.881416Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:22.707989Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:23.694942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:25.171887Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:26.554922Z | Info | Live bytes: 837.75MB Heap size: 2609.91MB +2024-07-22T12:01:27.611240Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:43.549107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:01:44.553070Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:04.661740Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:06.926682Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:07.419031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:12.088541Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:02:12.553539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:26.277485Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:26.566745Z | Info | Live bytes: 945.92MB Heap size: 2609.91MB +2024-07-22T12:02:31.362942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:41.692220Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:02:41.732754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:43.607948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:43.726427Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:02:44.092574Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:02:44.641079Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:09.155641Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:24.906969Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:25.668581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:26.568515Z | Info | Live bytes: 967.06MB Heap size: 2609.91MB +2024-07-22T12:03:27.180984Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:29.198688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:33.504876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:38.455102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:40.581573Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-22T12:03:42.299398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:03:42.446592Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:04:26.613463Z | Info | Live bytes: 974.81MB Heap size: 2609.91MB +2024-07-22T12:04:27.316780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:27.811675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:28.715527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:29.142031Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:29.752220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:30.270019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:30.713213Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:31.208507Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:31.711839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:04:33.528529Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:04:51.737594Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:05:02.720986Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:05:26.625991Z | Info | Live bytes: 811.00MB Heap size: 2609.91MB +2024-07-22T12:06:26.655486Z | Info | Live bytes: 811.00MB Heap size: 2609.91MB +2024-07-22T12:07:14.165802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:07:14.975290Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:07:15.891147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:07:26.665414Z | Info | Live bytes: 809.95MB Heap size: 2609.91MB +2024-07-22T12:08:21.706515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:22.625441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:22.792570Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:23.002084Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:23.782644Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:24.395030Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:25.107720Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:25.581970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:26.030556Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:26.538586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:26.666798Z | Info | Live bytes: 821.60MB Heap size: 2609.91MB +2024-07-22T12:08:27.038514Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:28.816489Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:31.158211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:31.946478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:31.952422Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:32.426313Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:32.510830Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:32.885533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:33.435149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:33.934874Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:35.073117Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:35.503539Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:36.145600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:36.517902Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:36.617137Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:36.683198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:36.736478Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:36.850886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:37.024384Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:37.109809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:37.575298Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:37.948103Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:38.379647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:40.363884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:40.935034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:41.566865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:43.216631Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:43.647283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:44.175899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:44.628650Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:45.110044Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:46.067968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:46.539926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:47.577664Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:48.981973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:49.350678Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:49.866512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:50.876732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:52.089135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:52.176125Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:52.395925Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:52.549154Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:52.563346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:52.700643Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:52.782360Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:52.843228Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:52.942215Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:53.068759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:53.200628Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:53.580704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:56.194738Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:56.397220Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:56.536971Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:58.246993Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:58.630297Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:58.731872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:08:59.053714Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:08:59.422447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:00.050047Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:00.415622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:01.369996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:01.789981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:02.113641Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:02.223752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:02.655987Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:03.028785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:03.136642Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:03.489542Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:03.510397Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:03.588001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:03.956460Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:04.542869Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:04.913786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:05.634370Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:05.762741Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:05.854556Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:06.009584Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:06.452867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:07.045908Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:07.051199Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:07.168702Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:07.249681Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:07.445403Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:07.543730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:07.561185Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:07.808895Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:08.099346Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:08.176185Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:08.479258Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:08.855955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:10.333817Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:10.413118Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:10.709809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:11.286569Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:11.721875Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:12.017623Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:12.299836Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:12.792895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:14.836663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:14.843689Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:15.053301Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:15.175529Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:15.236907Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:15.295096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:15.445036Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:15.539998Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:15.746586Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:15.809266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:16.294981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:17.115732Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:17.672433Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:17.673374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:17.762816Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:17.864424Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:18.121670Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:18.129911Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:18.200314Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:09:18.569080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:19.055341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:19.532321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:20.062368Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:20.499630Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:21.384557Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:22.892602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:23.434490Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:26.667578Z | Info | Live bytes: 548.77MB Heap size: 2614.10MB +2024-07-22T12:09:26.888776Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:28.979013Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:29.402706Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:30.195402Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:30.649398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:41.414965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:41.907058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:42.371090Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:42.914496Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:46.016283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:46.440486Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:47.102474Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:49.092225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:09:49.544274Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:09:50.122646Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:03.788395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:07.130632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:15.402051Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:26.675118Z | Info | Live bytes: 707.73MB Heap size: 2614.10MB +2024-07-22T12:10:39.864475Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:10:48.135915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:51.697272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:52.798244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:54.896331Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:55.952897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:57.702198Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:58.717688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:10:58.743628Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-22T12:10:59.859586Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:11:25.319342Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:11:25.561733Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:11:26.677810Z | Info | Live bytes: 714.98MB Heap size: 2614.10MB +2024-07-22T12:12:26.738887Z | Info | Live bytes: 716.01MB Heap size: 2614.10MB +2024-07-22T12:13:05.381959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:08.488502Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:09.012484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:09.668628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:10.148770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:11.311006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:11.810635Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:12.227973Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:12.940671Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:23.963259Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:13:24.167998Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:13:24.322813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:24.859504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:24.939608Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:13:25.311057Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:25.488763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:13:25.857276Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:26.740466Z | Info | Live bytes: 761.33MB Heap size: 2614.10MB +2024-07-22T12:13:29.892923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:30.326751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:54.042999Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:54.465649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:13:54.884849Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:14:04.606182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:06.527707Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:09.163782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:11.770264Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:11.904292Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:12.132034Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:17.939839Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:14:26.749940Z | Info | Live bytes: 838.83MB Heap size: 2614.10MB +2024-07-22T12:14:30.447730Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:30.513805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:30.597166Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:30.702572Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:30.762247Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:30.978684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:31.043722Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:31.140716Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:31.218395Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:31.293973Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:31.374535Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:31.409670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:31.728484Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:31.944927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:32.059249Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:32.118131Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:32.860649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:33.631896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:33.930078Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:34.141181Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:34.272669Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:34.321685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:34.403458Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:34.487673Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:34.803853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:35.976756Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:36.737211Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:14:37.198425Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:50.899680Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:51.038361Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:51.122175Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:51.247222Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:51.278573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:51.353500Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:51.436521Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:51.719239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:52.363389Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:52.708976Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:14:52.725940Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:53.295420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:55.552923Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:55.977059Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:56.644450Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:14:56.852962Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:15:22.217374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:15:22.639860Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:15:23.124554Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:15:26.754947Z | Info | Live bytes: 561.00MB Heap size: 2614.10MB +2024-07-22T12:16:26.790224Z | Info | Live bytes: 561.00MB Heap size: 2614.10MB +2024-07-22T12:16:55.226503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:04.540500Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:04.864051Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:17:04.943182Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:17:04.974003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:05.689193Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:17:06.058214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:06.366939Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:17:06.738073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:07.216526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:07.293600Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-22T12:17:08.731933Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:21.521320Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:22.137009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:22.741693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:23.025593Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-22T12:17:24.122186Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:17:26.795774Z | Info | Live bytes: 575.05MB Heap size: 2614.10MB +2024-07-22T12:18:26.857279Z | Info | Live bytes: 575.05MB Heap size: 2614.10MB +2024-07-22T12:19:26.916019Z | Info | Live bytes: 575.05MB Heap size: 2614.10MB +2024-07-22T12:20:26.956983Z | Info | Live bytes: 575.05MB Heap size: 2614.10MB +2024-07-22T12:21:05.975269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:21:26.974298Z | Info | Live bytes: 668.97MB Heap size: 2614.10MB +2024-07-22T12:21:27.380341Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:21:28.004942Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:21:54.695692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:21:57.508382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:57.668766Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:57.776626Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:57.867009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:21:57.897133Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:57.986127Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:58.060558Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:58.347537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:21:58.856388Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:59.135431Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:21:59.231399Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:21:59.643905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:22:27.002593Z | Info | Live bytes: 707.16MB Heap size: 2614.10MB +2024-07-22T12:22:28.009280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:22:28.603403Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:23:04.044611Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:23:04.720477Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:23:27.025839Z | Info | Live bytes: 710.16MB Heap size: 2614.10MB +2024-07-22T12:24:27.086453Z | Info | Live bytes: 710.16MB Heap size: 2614.10MB +2024-07-22T12:25:27.123697Z | Info | Live bytes: 716.26MB Heap size: 2614.10MB +2024-07-22T12:26:26.888652Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:27.125584Z | Info | Live bytes: 716.26MB Heap size: 2614.10MB +2024-07-22T12:26:28.691708Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:30.390285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:31.468289Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:34.842865Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:48.249607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:48.726528Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:49.151190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:50.146915Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:50.940328Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:51.383135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:51.843564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:52.633685Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:26:52.929075Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:53.366401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:53.691417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T12:26:53.975318Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:54.518807Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:26:55.004010Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:27:00.992649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:27:15.103797Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:27:16.141995Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T12:27:27.138515Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:28:27.170973Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:29:27.230524Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:30:27.291939Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:31:27.325994Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:32:27.387318Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:33:27.448617Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:34:27.509704Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:35:27.570508Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:36:27.601625Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:37:27.662903Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:38:27.685264Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:39:27.746668Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:40:27.808229Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:41:27.869419Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:42:27.930862Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:43:27.991441Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:44:28.022039Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:45:28.082751Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:46:28.127204Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:47:28.151354Z | Info | Live bytes: 788.16MB Heap size: 2614.10MB +2024-07-22T12:48:05.532260Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:48:09.803660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:48:10.280197Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:48:10.902205Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:48:14.457217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T12:48:28.163616Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:49:28.197674Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:50:28.258645Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:51:28.271564Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:52:28.307671Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:53:28.368916Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:54:28.429319Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:55:28.459469Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:56:28.520626Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:57:28.561210Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:58:28.622417Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T12:59:28.681667Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:00:28.685138Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:01:28.745269Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:14:12.858501Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:15:12.860382Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:16:12.914559Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:17:12.976023Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:18:12.997363Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:19:13.058813Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:20:13.098674Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:21:13.145234Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:22:13.206521Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:23:13.245402Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:24:13.306896Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:25:13.368514Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:26:13.397199Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:27:13.452812Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:28:13.471865Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:29:13.533195Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:30:13.581465Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:31:13.642648Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:32:13.703935Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:33:13.765239Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:34:13.825287Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:35:13.886045Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:36:13.946326Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:37:14.006328Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:38:14.056017Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:39:14.116283Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:40:14.170232Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:41:14.230398Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:42:14.291245Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:43:14.352148Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:44:14.363456Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:45:14.423186Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:46:14.483349Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:47:14.542230Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:48:14.603389Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:49:14.650649Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:50:14.711333Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:51:14.757655Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:52:14.808235Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:53:14.819466Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:54:14.857481Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:55:14.874151Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:56:14.934313Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:57:14.971639Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:58:15.032280Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T13:59:15.083813Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:00:15.145003Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:01:15.205182Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:02:15.265786Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:03:15.326466Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:04:15.382741Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:05:15.443939Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:06:15.505808Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:07:15.543366Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:08:15.604507Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:09:15.665261Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:10:15.725394Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:11:15.777918Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:12:15.834415Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:13:15.895465Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:14:15.956614Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:15:16.017359Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:16:16.071363Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:17:16.128932Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:18:16.189375Z | Info | Live bytes: 816.54MB Heap size: 2614.10MB +2024-07-22T14:18:34.986741Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:19:16.229188Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:20:16.289157Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:20:20.374288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:21:16.349671Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:22:16.410293Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:23:16.455916Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:24:16.516289Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:25:16.577175Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:26:16.637304Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:27:16.697264Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:28:16.757395Z | Info | Live bytes: 883.63MB Heap size: 2614.10MB +2024-07-22T14:28:23.331435Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T14:28:28.157309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:28:28.847427Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:28:30.803203Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:28:32.319535Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:28:36.091007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:28:37.126322Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:28:37.259195Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:28:37.341608Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:28:37.512711Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:28:37.513634Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:28:38.284881Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T14:28:38.320884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:28:38.740143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:29:10.688728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:29:16.786659Z | Info | Live bytes: 986.62MB Heap size: 2614.10MB +2024-07-22T14:29:55.140225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:29:59.885015Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:00.036203Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:00.205551Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:00.236751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:00.338990Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:00.436772Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:00.509041Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:00.721970Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:01.730341Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:01.800693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:01.855894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:02.229050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:02.343851Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:02.537090Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:02.713991Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:02.728255Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:03.036417Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:03.237626Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:03.380099Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:03.416309Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:03.487341Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:03.860968Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:04.380050Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:04.978207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:06.394693Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:06.829398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:07.971998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:08.597225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:09.068041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:09.305913Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:09.432192Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:09.507441Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:09.576519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:10.006453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:12.836689Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:12.966536Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:13.084001Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-22T14:30:13.280629Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:16.792032Z | Info | Live bytes: 1037.16MB Heap size: 2614.10MB +2024-07-22T14:30:17.847184Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:18.939657Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:19.643035Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:20.596088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:21.035964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:21.754668Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:22.179619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:22.434528Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T14:30:23.021018Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:35.065619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:30:35.380007Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T14:31:16.834682Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:32:16.863399Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:33:16.924557Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:34:16.986142Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:35:17.047642Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:36:17.108238Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:37:17.169241Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:38:17.219773Z | Info | Live bytes: 600.90MB Heap size: 2647.65MB +2024-07-22T14:38:55.360444Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:39:01.922262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:39:09.167424Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-07-22T14:39:09.978508Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:39:17.226184Z | Info | Live bytes: 985.25MB Heap size: 2668.63MB +2024-07-22T14:40:12.192126Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-22T14:40:12.192960Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T14:40:12.239000Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:40:17.231275Z | Info | Live bytes: 985.25MB Heap size: 2668.63MB +2024-07-22T14:40:17.269374Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:40:18.913088Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:40:35.864686Z | Info | Load cabal cradle using single file +2024-07-22T14:40:36.974899Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT135003-198 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T14:40:51.989988Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:41:17.251393Z | Info | Live bytes: 1036.63MB Heap size: 2668.63MB +2024-07-22T14:41:33.641538Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:41:44.339926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:41:47.718452Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:41:49.680091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:42:09.749939Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-b64d5d4bf1c53479da99db7b8e4b94e89463fe75 +2024-07-22T14:42:09.750211Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-b64d5d4bf1c53479da99db7b8e4b94e89463fe75 +2024-07-22T14:42:09.756410Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.0.0.0-inplace-internal + , cardano-api-9.1.0.0-inplace ] +2024-07-22T14:42:10.422926Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Tx.hs +2024-07-22T14:42:10.423521Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T14:42:11.988987Z | Info | Load cabal cradle using single file +2024-07-22T14:42:13.057697Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT135003-202 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T14:42:17.020750Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:17.026982Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.1.0.0-inplace-internal] +2024-07-22T14:42:17.258307Z | Info | Live bytes: 1020.74MB Heap size: 2860.52MB +2024-07-22T14:42:17.447377Z | Info | Cradle path: cardano-api/src/Cardano/Api/Byron.hs +2024-07-22T14:42:17.447939Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T14:42:19.055878Z | Info | Load cabal cradle using single file +2024-07-22T14:42:20.195090Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT135003-203 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T14:42:24.103648Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-b64d5d4bf1c53479da99db7b8e4b94e89463fe75 +2024-07-22T14:42:24.103957Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-b64d5d4bf1c53479da99db7b8e4b94e89463fe75 +2024-07-22T14:42:24.110680Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.1.0.0-inplace + , cardano-api-9.1.0.0-inplace-internal ] +2024-07-22T14:42:24.774137Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-22T14:42:24.774578Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T14:42:26.354844Z | Info | Load cabal cradle using single file +2024-07-22T14:42:27.408182Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT135003-204 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T14:42:31.241410Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:31.241939Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:31.242348Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:31.248016Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.1.0.0-inplace + , cardano-api-9.1.0.0-inplace-internal ] +2024-07-22T14:42:31.926150Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Eras.hs +2024-07-22T14:42:31.926682Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-22T14:42:33.507328Z | Info | Load cabal cradle using single file +2024-07-22T14:42:34.597426Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT135003-205 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-22T14:42:38.512009Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:38.512695Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:38.513212Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:38.513857Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-7e03621df479a74bae05449574990c6a8ebfa0d8 +2024-07-22T14:42:38.524156Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.1.0.0-inplace + , cardano-api-9.1.0.0-inplace-internal ] +2024-07-22T14:43:17.296550Z | Info | Live bytes: 1461.74MB Heap size: 3027.24MB +2024-07-22T14:44:17.345818Z | Info | Live bytes: 1461.74MB Heap size: 3027.24MB +2024-07-22T14:45:17.348187Z | Info | Live bytes: 1461.74MB Heap size: 3027.24MB +2024-07-22T14:45:29.440325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:46:17.378549Z | Info | Live bytes: 1025.10MB Heap size: 3484.42MB +2024-07-22T14:46:28.897391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:46:55.963157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:47:03.328264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:47:14.182868Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:47:17.381269Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:48:17.433184Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:49:17.490649Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:50:17.552193Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:51:17.593415Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:52:17.654629Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:52:21.002239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:52:22.276996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T14:53:17.709636Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:54:17.762641Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:55:17.824184Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:56:17.847355Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:57:17.908847Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:58:17.970661Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T14:59:18.032247Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:00:18.071213Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:01:18.132542Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:02:18.193900Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:03:18.255158Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:04:18.316277Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:05:18.357421Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:06:18.418561Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:07:18.452613Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:08:18.514037Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:09:18.554986Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:10:18.615870Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:11:18.642552Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:12:18.703289Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:13:18.764182Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:14:18.825401Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:15:18.886842Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:16:18.890457Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:17:18.902244Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:18:18.922653Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:19:18.962616Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:20:19.023987Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:21:17.199624Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T15:21:19.062815Z | Info | Live bytes: 1086.03MB Heap size: 3484.42MB +2024-07-22T15:21:32.534890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T15:22:19.117247Z | Info | Live bytes: 1114.09MB Heap size: 3484.42MB +2024-07-22T15:22:26.450250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T15:22:26.932907Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-22T15:23:19.126397Z | Info | Live bytes: 1238.80MB Heap size: 3484.42MB +2024-07-22T15:23:20.116616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-22T15:24:19.156715Z | Info | Live bytes: 1238.80MB Heap size: 3484.42MB +2024-07-22T15:25:19.194693Z | Info | Live bytes: 1238.80MB Heap size: 3484.42MB +2024-07-22T15:26:19.246229Z | Info | Live bytes: 1238.80MB Heap size: 3484.42MB +2024-07-22T15:27:19.250318Z | Info | Live bytes: 1238.80MB Heap size: 3484.42MB +2024-07-22T15:28:19.300045Z | Info | Live bytes: 1238.80MB Heap size: 3484.42MB +2024-07-22T15:28:51.052836Z | Info | LSP: received shutdown +2024-07-22T15:28:51.055923Z | Error | Got EOF +2024-07-23 07:14:24.2930000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-23 07:14:24.2950000 [client] INFO Finding haskell-language-server +2024-07-23 07:14:24.2980000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.2980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.3030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-23 07:14:24.4500000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.4500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.4560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-23 07:14:24.6000000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.6010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.6060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-23 07:14:24.7520000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.7530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.7580000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-23 07:14:24.8680000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.8680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.8720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-23 07:14:24.8890000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.8890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.8940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-23 07:14:24.9080000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.9090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.9150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-23 07:14:24.9330000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-23 07:14:24.9690000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:24.9690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:24.9750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-23 07:14:25.0860000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-23 07:14:25.0870000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-23 07:14:47.8260000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-23 07:14:48.0030000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-23 07:14:48.0030000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:48.0030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:48.0070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-23 07:14:48.0810000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:48.0810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:48.0850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-23 07:14:48.1010000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:48.1010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:48.1050000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-23 07:14:48.1180000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:48.1180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:48.1220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-23 07:14:48.1360000 [client] INFO Checking for ghcup installation +2024-07-23 07:14:48.1360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 07:14:48.1400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-23 07:14:48.2340000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-23 07:14:48.2340000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-23 07:14:48.2340000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-23 07:14:48.2340000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-23 07:14:48.2340000 [client] INFO server environment variables: +2024-07-23 07:14:48.2340000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-23 07:14:48.2340000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-23 07:14:48.2340000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-23 07:14:48.2350000 [client] INFO Starting language server +2024-07-23T07:14:57.250911Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-23T07:14:57.251943Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-23T07:14:57.252268Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-23T07:14:57.254937Z | Info | Logging heap statistics every 60.00s +2024-07-23T07:14:57.261591Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-23T07:14:57.261972Z | Info | Starting server +2024-07-23T07:14:57.263701Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-23T07:14:57.332511Z | Info | Started LSP server in 0.07s +2024-07-23T07:14:58.719720Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-23T07:14:58.720650Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-23T07:14:59.316582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T07:15:00.269022Z | Info | Load cabal cradle using single file +2024-07-23T07:15:01.260679Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT18183-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-23T07:15:09.026613Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-4680c848285cdcb20b8c192b1586026351591b55 +2024-07-23T07:15:09.033822Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-23T07:15:57.263510Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:16:57.309530Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:17:57.370152Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:18:57.404092Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:19:57.464612Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:20:57.483515Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:21:57.524019Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:22:57.584633Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:23:57.645560Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:24:57.705378Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:25:57.765752Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:26:57.825440Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:27:57.885833Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:28:57.900704Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:29:57.960574Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:30:58.021402Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:31:58.081997Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:32:58.142558Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:33:58.198074Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:34:58.258597Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:35:58.319128Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:36:58.379663Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:37:58.440196Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:38:58.500698Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:39:58.505206Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:40:58.565835Z | Info | Live bytes: 333.78MB Heap size: 1853.88MB +2024-07-23T07:41:31.885858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T07:41:53.688478Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T07:41:58.567444Z | Info | Live bytes: 485.01MB Heap size: 1853.88MB +2024-07-23T07:42:58.627374Z | Info | Live bytes: 485.01MB Heap size: 1853.88MB +2024-07-23T07:43:58.637544Z | Info | Live bytes: 485.01MB Heap size: 1853.88MB +2024-07-23T07:44:58.698135Z | Info | Live bytes: 485.01MB Heap size: 1853.88MB +2024-07-23T07:45:58.758541Z | Info | Live bytes: 485.01MB Heap size: 1853.88MB +2024-07-23T07:46:58.818587Z | Info | Live bytes: 485.01MB Heap size: 1853.88MB +2024-07-23T07:47:14.479994Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T07:47:58.858391Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:48:58.918853Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:49:58.967216Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:50:59.023908Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:51:59.084459Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:52:59.144393Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:53:59.204429Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:54:59.234212Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:55:59.264824Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:56:59.324505Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:57:59.384591Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:58:59.421539Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T07:59:59.482161Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:00:59.542499Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:01:59.602610Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:02:59.662436Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:03:59.667627Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:04:59.717146Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:05:59.777609Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:06:59.838271Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:07:59.898698Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:08:59.959225Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:10:00.019754Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:11:00.040402Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:12:00.056032Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:13:00.059996Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:14:00.069558Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:15:00.130155Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:16:00.190671Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:17:00.251172Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:18:00.311581Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:19:00.372164Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:20:00.385739Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:21:00.446242Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:22:00.506531Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:23:00.529639Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:24:00.564332Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:25:00.624491Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:26:00.684522Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:27:00.688935Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:28:00.724085Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:29:00.752302Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:30:00.775514Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:32:51.162540Z | Info | Live bytes: 571.58MB Heap size: 1853.88MB +2024-07-23T08:33:34.933330Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:33:35.717861Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:33:41.296294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:33:50.482771Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:33:51.164193Z | Info | Live bytes: 624.79MB Heap size: 1853.88MB +2024-07-23T08:33:51.244851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:33:51.398904Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-23T08:34:51.171553Z | Info | Live bytes: 624.79MB Heap size: 1853.88MB +2024-07-23T08:35:51.184386Z | Info | Live bytes: 624.79MB Heap size: 1853.88MB +2024-07-23T08:36:51.244959Z | Info | Live bytes: 624.79MB Heap size: 1853.88MB +2024-07-23T08:37:51.305672Z | Info | Live bytes: 624.79MB Heap size: 1853.88MB +2024-07-23T08:38:51.365226Z | Info | Live bytes: 624.79MB Heap size: 1853.88MB +2024-07-23T08:38:58.576683Z | Error | Got EOF +2024-07-23 08:49:26.2870000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-23 08:49:26.2880000 [client] INFO Finding haskell-language-server +2024-07-23 08:49:26.2900000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:26.2900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:26.2960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-23 08:49:27.1320000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:27.1320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:27.1400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-23 08:49:27.3760000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:27.3760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:27.3830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-23 08:49:27.5600000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:27.5600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:27.5670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-23 08:49:27.7530000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:27.7530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:27.7600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-23 08:49:27.7790000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:27.7790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:27.7910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-23 08:49:27.8060000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:27.8060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:27.8130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-23 08:49:27.8360000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-23 08:49:27.9910000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:27.9910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:27.9970000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-23 08:49:28.1650000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-23 08:49:28.1660000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-23 08:49:37.4300000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-23 08:49:37.8950000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-23 08:49:37.8950000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:37.8950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:37.9010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-23 08:49:37.9860000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:37.9860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:37.9900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-23 08:49:38.0050000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:38.0050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:38.0100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-23 08:49:38.0230000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:38.0230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:38.0270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-23 08:49:38.0410000 [client] INFO Checking for ghcup installation +2024-07-23 08:49:38.0410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-23 08:49:38.0450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-23 08:49:38.1400000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-23 08:49:38.1400000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-23 08:49:38.1400000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-23 08:49:38.1400000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-23 08:49:38.1400000 [client] INFO server environment variables: +2024-07-23 08:49:38.1410000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-23 08:49:38.1410000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-23 08:49:38.1410000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-23 08:49:38.1420000 [client] INFO Starting language server +2024-07-23T08:49:48.626774Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-23T08:49:48.628893Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-23T08:49:48.629128Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-23T08:49:48.632885Z | Info | Logging heap statistics every 60.00s +2024-07-23T08:49:48.640858Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-23T08:49:48.641285Z | Info | Starting server +2024-07-23T08:49:48.655703Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-23T08:49:48.776782Z | Info | Started LSP server in 0.14s +2024-07-23T08:49:50.125465Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs +2024-07-23T08:49:50.126044Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-23T08:49:50.709157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:49:51.692972Z | Info | Load cabal cradle using single file +2024-07-23T08:49:52.854123Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT9965-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-23T08:49:56.967944Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-4680c848285cdcb20b8c192b1586026351591b55 +2024-07-23T08:49:56.974637Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-23T08:49:59.430961Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:50:00.027870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-23T08:50:01.409541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:50:48.651384Z | Info | Live bytes: 467.64MB Heap size: 1752.17MB +2024-07-23T08:51:48.712146Z | Info | Live bytes: 467.64MB Heap size: 1752.17MB +2024-07-23T08:52:48.742367Z | Info | Live bytes: 467.64MB Heap size: 1752.17MB +2024-07-23T08:53:48.781336Z | Info | Live bytes: 467.64MB Heap size: 1752.17MB +2024-07-23T08:54:48.797172Z | Info | Live bytes: 467.64MB Heap size: 1752.17MB +2024-07-23T08:55:29.427780Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:55:29.850203Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-23T08:55:36.454234Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-23T08:55:36.501692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T08:55:48.810522Z | Info | Live bytes: 433.45MB Heap size: 1940.91MB +2024-07-23T08:56:48.852394Z | Info | Live bytes: 433.45MB Heap size: 1940.91MB +2024-07-23T08:57:48.883290Z | Info | Live bytes: 433.45MB Heap size: 1940.91MB +2024-07-23T08:58:48.943775Z | Info | Live bytes: 433.45MB Heap size: 1940.91MB +2024-07-23T08:59:48.974803Z | Info | Live bytes: 433.45MB Heap size: 1940.91MB +2024-07-23T09:00:49.029951Z | Info | Live bytes: 433.45MB Heap size: 1940.91MB +2024-07-23T09:01:49.040413Z | Info | Live bytes: 433.45MB Heap size: 1940.91MB +2024-07-23T09:02:06.706513Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:02:08.205140Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-23T09:02:10.567691Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:02:12.082215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:02:21.638527Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:02:22.468417Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:02:23.500077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:02:23.617138Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-23T09:02:49.066312Z | Info | Live bytes: 435.57MB Heap size: 1940.91MB +2024-07-23T09:03:49.070306Z | Info | Live bytes: 435.57MB Heap size: 1940.91MB +2024-07-23T09:04:49.116387Z | Info | Live bytes: 435.57MB Heap size: 1940.91MB +2024-07-23T09:05:49.176173Z | Info | Live bytes: 435.57MB Heap size: 1940.91MB +2024-07-23T09:06:49.192089Z | Info | Live bytes: 435.57MB Heap size: 1940.91MB +2024-07-23T09:07:06.392340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:16.169822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:16.852529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:17.676192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:18.347217Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-23T09:07:20.333688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:27.981839Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:42.325602Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:43.049147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:49.193571Z | Info | Live bytes: 479.98MB Heap size: 1940.91MB +2024-07-23T09:07:50.522057Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-23T09:07:50.706170Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-23T09:07:51.007659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:51.305123Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-23T09:07:51.814253Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:07:52.155417Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-23T09:08:04.652759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:08:05.418315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:08:06.278284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:08:06.611517Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-23T09:08:49.230282Z | Info | Live bytes: 498.36MB Heap size: 1940.91MB +2024-07-23T09:09:17.186001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:17.860171Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:18.434316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:23.374401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:32.510768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:33.444879Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:34.544751Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:35.574960Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:09:36.370655Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ ] +2024-07-23T09:09:49.243681Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:10:49.304388Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:11:49.318726Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:12:49.326418Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:13:49.387103Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:14:49.447319Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:15:49.498685Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:16:49.559358Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:17:49.619999Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:18:49.634272Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:19:49.655409Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:20:49.702358Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:21:49.733548Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:22:49.793405Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:23:49.818016Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:24:47.768791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:24:49.820413Z | Info | Live bytes: 514.26MB Heap size: 1940.91MB +2024-07-23T09:24:52.253340Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-23T09:25:49.842394Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:26:49.903124Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:27:49.963800Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:28:50.024457Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:29:50.085127Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:30:50.126479Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:50:22.434326Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:51:22.475654Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:52:22.535337Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:53:22.567757Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:54:22.621802Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:55:22.682495Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:56:22.743090Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:57:22.794985Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:58:22.855623Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T09:59:22.916237Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:00:22.951433Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:01:23.011322Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:02:23.071883Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:03:23.132356Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:04:23.192961Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:05:23.253598Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:06:23.254504Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:07:23.315182Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:08:23.367221Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:09:23.382581Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:10:23.440726Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:11:23.473003Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:12:23.533670Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:13:23.587313Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:14:23.602279Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:15:23.616866Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:16:23.621076Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:17:23.651617Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:18:23.678560Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:19:23.739268Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:20:23.778346Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:21:23.814541Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:22:23.875159Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:23:23.918512Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:24:23.937913Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:25:23.942423Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:26:24.003066Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:27:24.006470Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:28:24.046572Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:29:24.054182Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:30:24.088877Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:31:24.095810Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:32:24.118531Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:33:24.142267Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:34:24.182530Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:35:24.214520Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:36:24.275177Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:37:24.278550Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:38:24.336522Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:39:24.392511Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:40:24.407487Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:41:24.420175Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:42:24.480586Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:43:24.529659Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:44:24.587316Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:45:24.588738Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:46:24.649182Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:47:24.654227Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:48:24.714659Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:49:24.774887Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:50:24.823028Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:51:24.869665Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:52:24.872718Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:53:24.879256Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:54:24.886398Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:55:24.946801Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:56:25.007181Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:57:25.067576Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:58:25.127947Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T10:59:25.144554Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:00:25.205100Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:01:25.238616Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:02:25.262519Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:03:25.314719Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:04:25.375306Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:05:25.435948Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:06:25.486524Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:07:25.520644Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:08:25.570210Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:09:25.598434Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:10:25.621522Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:11:25.681295Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:12:25.741673Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:13:25.802056Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:14:25.862445Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:15:25.922781Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:16:25.952049Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:17:25.981980Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:18:26.012861Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:19:26.070433Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:20:26.098082Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:21:26.098675Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:22:26.155989Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:23:26.216230Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:24:26.230372Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:25:26.290780Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:26:26.310438Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:27:26.326363Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:28:26.358443Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:29:26.402529Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:30:26.463109Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:31:26.474572Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:32:26.532517Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:33:26.586367Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:34:26.647020Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:35:26.650163Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:36:26.710725Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:37:26.744701Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:38:26.791463Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:39:26.803923Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:40:26.806551Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:41:26.867343Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:42:26.928053Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:43:26.988847Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:44:27.049522Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:45:27.094468Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:46:27.155239Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:47:27.215973Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:48:27.253070Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:49:27.286488Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:50:27.287275Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:51:27.347992Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:52:27.382554Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:53:27.443207Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:54:27.503854Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:55:27.564166Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:56:27.604602Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:57:27.665365Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:58:27.678608Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T11:59:27.718535Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:00:27.779286Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:01:27.839954Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:02:27.900696Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:03:27.960458Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:04:28.021227Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:05:28.082000Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:06:28.096576Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:07:28.118386Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:08:28.135615Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:09:28.196258Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:10:28.256907Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:11:28.317553Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:12:28.373633Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:13:28.423233Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:14:28.470488Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:15:28.527119Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:16:28.587791Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:17:28.648412Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:18:28.708416Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:19:28.768987Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:20:28.790510Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:21:28.851127Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:22:28.869734Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:23:28.872757Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:24:28.881594Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:25:28.886566Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:26:28.947212Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:27:29.007717Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:28:29.046562Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:29:29.107218Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:30:29.167798Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:31:29.228476Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:32:29.261756Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:33:29.322372Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:34:29.383002Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:35:29.400903Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:36:29.461538Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:37:29.463094Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:38:29.523780Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:39:29.526563Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:40:29.565398Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:41:29.624463Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:42:29.680870Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:43:29.711958Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:44:29.769863Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:45:29.774801Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:46:29.803373Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:47:29.864054Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:48:29.924408Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:49:29.951405Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:50:30.011789Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:51:30.072394Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:52:30.132981Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:53:30.158493Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:54:30.190461Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:55:30.238815Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:56:30.282088Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:57:30.342762Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:58:30.395689Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T12:59:30.456260Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:00:30.511788Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:01:30.555080Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:02:30.582554Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:03:30.643181Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:04:30.664454Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:05:30.678531Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:06:30.739201Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:07:30.799833Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:08:30.815715Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:09:30.870521Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:10:30.902553Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:11:30.962701Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:12:31.023293Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:13:31.035567Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:14:31.096183Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:15:31.152857Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:16:31.213505Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:17:31.273991Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:18:31.334546Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:19:31.359035Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:20:31.414506Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:21:31.474984Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:22:31.519934Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:23:31.574529Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:24:31.634997Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:25:31.638484Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:26:31.699194Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:27:31.734510Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:28:31.752171Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:29:31.766505Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:30:31.827225Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:31:31.887432Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:32:31.947986Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:33:32.003990Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:34:32.064518Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:35:32.086582Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:36:32.147221Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:37:32.207820Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:38:32.261759Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:39:32.279270Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:40:32.303131Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:41:32.362879Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:42:32.423426Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:43:32.437360Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:44:32.497856Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:45:32.558191Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:46:32.610329Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:47:32.670799Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:48:32.731323Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:49:32.758392Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:50:32.804523Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:51:32.805106Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:52:32.815501Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:53:32.870600Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:54:32.912606Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:55:32.972293Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:56:33.032341Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:57:33.064140Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:58:33.099200Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T13:59:33.159522Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:00:33.220181Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:01:33.278683Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:02:33.284078Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:03:33.344264Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:04:33.404240Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:05:33.464293Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:06:33.524434Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:07:33.584283Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:08:33.644298Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:09:33.704220Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:10:33.764272Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:11:33.824331Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:12:33.884281Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:13:33.944390Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:14:34.004351Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:15:34.038340Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:16:34.098827Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:17:34.152412Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:18:34.212239Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:19:34.272324Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:20:34.332352Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:21:34.352815Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:22:34.413298Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:23:34.473248Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:24:34.533311Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:25:34.593419Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:26:34.653317Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:27:34.713229Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:28:34.773338Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:29:34.828965Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:30:34.889481Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:31:34.949358Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:32:35.003292Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:33:35.063408Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:34:35.104217Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:35:35.159562Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:36:35.219235Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:37:35.279286Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:38:35.315481Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:39:35.375228Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:40:35.435367Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:41:35.495346Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:42:35.555401Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:43:35.570180Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:44:35.625446Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:45:35.668262Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:46:35.714409Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:47:35.775171Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:48:35.835437Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:49:35.862250Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:50:35.904144Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:51:35.947245Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:52:35.999709Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:53:36.059241Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:54:36.119248Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:55:36.179704Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:56:36.184435Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:57:36.198365Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:58:36.258895Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T14:59:36.302440Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T15:00:36.361248Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T15:01:36.374457Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T15:02:36.406597Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T15:03:36.462373Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T15:04:36.522894Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T15:05:36.584946Z | Info | Live bytes: 534.81MB Heap size: 1940.91MB +2024-07-23T15:06:07.308849Z | Info | LSP: received shutdown +2024-07-23T15:06:07.336806Z | Error | Got EOF +2024-07-24 07:59:20.3290000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-24 07:59:20.3400000 [client] INFO Finding haskell-language-server +2024-07-24 07:59:20.3410000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:20.3410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:20.3470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-24 07:59:20.6570000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:20.6570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:20.6620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-24 07:59:20.8380000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:20.8380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:20.8430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-24 07:59:20.9700000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:20.9700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:20.9740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-24 07:59:21.0840000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:21.0840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:21.0880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-24 07:59:21.1020000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:21.1020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:21.1060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-24 07:59:21.1200000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:21.1200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:21.1240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-24 07:59:21.1420000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-24 07:59:21.1730000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:21.1730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:21.1780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-24 07:59:21.2930000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-24 07:59:21.2940000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-24 07:59:43.1890000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-07-24 07:59:43.4250000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-24 07:59:43.4250000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:43.4250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:43.4300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-24 07:59:43.5140000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:43.5140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:43.5190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-24 07:59:43.5390000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:43.5390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:43.5440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-24 07:59:43.5590000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:43.5590000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:43.5630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-07-24 07:59:43.5780000 [client] INFO Checking for ghcup installation +2024-07-24 07:59:43.5790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 07:59:43.5840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-07-24 07:59:43.6900000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-24 07:59:43.6900000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-24 07:59:43.6900000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-24 07:59:43.6900000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-24 07:59:43.6900000 [client] INFO server environment variables: +2024-07-24 07:59:43.6900000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-24 07:59:43.6900000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-24 07:59:43.6900000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-24 07:59:43.6910000 [client] INFO Starting language server +2024-07-24T08:00:06.103349Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-07-24T08:00:06.104673Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-24T08:00:06.104971Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T08:00:06.107910Z | Info | Logging heap statistics every 60.00s +2024-07-24T08:00:06.118279Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T08:00:06.118823Z | Info | Starting server +2024-07-24T08:00:06.120739Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-24T08:00:06.344086Z | Info | Started LSP server in 0.23s +2024-07-24T08:00:07.705650Z | Info | Cradle path: cardano-api/internal/Cardano/Api/DRepMetadata.hs +2024-07-24T08:00:07.706732Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-24T08:00:08.220446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:00:09.387830Z | Info | Load cabal cradle using single file +2024-07-24T08:00:10.539750Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT176934-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-07-24T08:01:06.133687Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:02:06.193501Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:03:06.235551Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:04:06.295513Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:05:06.330199Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:06:06.369403Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:07:06.429498Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:08:06.490303Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:09:06.550374Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:10:06.610968Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:11:06.671762Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:11:43.309168Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-38b619f1c9b7be1ee3848670d3bd96b585a13082 +2024-07-24T08:11:43.313171Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-24T08:12:06.694385Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:13:06.755178Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:14:06.810745Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:15:06.871306Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:16:06.931454Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:17:06.991961Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:18:07.027603Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:19:07.076560Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:20:07.085515Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:21:07.140745Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:22:07.200521Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:23:07.260400Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:24:07.310121Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:25:07.370906Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:26:07.428925Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:27:07.437847Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:28:07.498542Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:29:07.559232Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:30:07.594290Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:31:07.629160Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:32:07.689505Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:33:07.750032Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:34:07.784599Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:35:07.816649Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:36:07.877199Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:36:48.344581Z | Warning | LSP: no handler for: "$/setTrace" +2024-07-24T08:36:53.132520Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:37:07.890537Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:38:07.951262Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:39:07.965204Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:40:07.981558Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:41:08.041409Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:42:08.101389Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:43:08.161334Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-07-24T08:43:39.868662Z | Info | LSP: received shutdown +2024-07-24T08:43:39.872092Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-07-24T08:43:39.872374Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-07-24T08:43:39.872531Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-07-24T08:43:39.872682Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-07-24T08:43:39.874819Z | Error | Got EOF +2024-07-24T08:48:26.102406Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-07-24T08:48:26.103759Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-24T08:48:26.104360Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T08:48:26.111743Z | Info | Logging heap statistics every 60.00s +2024-07-24T08:48:26.122232Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T08:48:26.122888Z | Info | Starting server +2024-07-24T08:48:26.125432Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-24T08:48:26.129271Z | Info | Started LSP server in 0.01s +2024-07-24T08:48:28.192157Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Tx.hs +2024-07-24T08:48:28.193427Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-24T08:48:28.733613Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:48:30.435020Z | Info | Load cabal cradle using single file +2024-07-24T08:48:32.004676Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT258318-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-07-24T08:48:37.519874Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-38b619f1c9b7be1ee3848670d3bd96b585a13082 +2024-07-24T08:48:37.524473Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-24T08:49:26.146527Z | Info | Live bytes: 760.91MB Heap size: 1952.45MB +2024-07-24T08:49:33.221356Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:49:33.664550Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T08:49:38.150558Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:49:48.180884Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:49:50.625172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:49:55.495210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:49:58.760111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:49:59.337565Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:50:00.370950Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:50:04.664985Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:50:26.163458Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:51:26.164146Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:52:26.224354Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:53:26.284348Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:54:26.344351Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:55:26.404544Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:56:26.464362Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:57:26.524520Z | Info | Live bytes: 781.00MB Heap size: 2060.45MB +2024-07-24T08:57:44.490548Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:57:45.340166Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:57:45.706023Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T08:57:46.376177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:57:48.228922Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T08:58:19.432621Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T08:58:26.532361Z | Info | Live bytes: 783.69MB Heap size: 2060.45MB +2024-07-24T08:59:26.592337Z | Info | Live bytes: 783.69MB Heap size: 2060.45MB +2024-07-24T09:00:26.618533Z | Info | Live bytes: 783.69MB Heap size: 2060.45MB +2024-07-24T09:00:46.211714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:00:46.876484Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:00:47.385042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:00:47.966928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:00:48.770506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:01:26.651821Z | Info | Live bytes: 799.75MB Heap size: 2060.45MB +2024-07-24T09:02:26.671529Z | Info | Live bytes: 799.75MB Heap size: 2060.45MB +2024-07-24T09:02:49.608120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:02:50.496187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:02:50.550163Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:03:26.705467Z | Info | Live bytes: 799.75MB Heap size: 2060.45MB +2024-07-24T09:03:44.853283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:03:45.423224Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:03:45.431229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:03:48.721073Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:03:53.040005Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:03:55.043106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:03:55.421302Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:03:55.549972Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:03:56.220207Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:03:56.349865Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:04:16.789770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:17.259650Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:04:17.294697Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:04:26.715279Z | Info | Live bytes: 599.18MB Heap size: 2422.21MB +2024-07-24T09:04:33.843143Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:04:34.158566Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:34.717195Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:36.707966Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:37.245712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:04:37.364696Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:38.181667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:38.893039Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:39.780487Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:40.470670Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:41.116227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:41.705730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:04:41.833343Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:04:42.404187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:05:26.760509Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:06:26.820374Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:07:26.880458Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:08:26.940406Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:09:27.000488Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:10:27.058390Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:11:27.095369Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:12:27.127872Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:13:27.187434Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:14:27.247476Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:15:27.307399Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:16:27.367334Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:17:27.427411Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:18:27.487391Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:19:27.499151Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:20:27.559391Z | Info | Live bytes: 594.54MB Heap size: 2422.21MB +2024-07-24T09:21:11.852695Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:21:27.560219Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:22:27.620422Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:23:27.680342Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:24:27.740333Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:25:27.800470Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:26:27.801307Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:27:27.861584Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:28:27.921394Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:29:27.981500Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:30:28.041314Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:31:28.101420Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:32:28.161557Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:33:28.221380Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:34:28.281369Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:35:28.341448Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:36:28.401466Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:37:28.461413Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:38:28.492412Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:39:28.552577Z | Info | Live bytes: 629.86MB Heap size: 2422.21MB +2024-07-24T09:39:49.245074Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:39:51.087038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:39:56.941930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:39:59.503802Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:01.984689Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:02.429150Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:06.493899Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:09.584867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:10.476581Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:10.566960Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:10.633487Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:10.776144Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:10.928453Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:11.523857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:12.137458Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:12.614339Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:12.676208Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:13.482848Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:14.433669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:14.889831Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:15.031975Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:15.352232Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:15.815137Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:40:15.920779Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:16.487752Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:25.763890Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:26.868986Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:27.012785Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:27.093747Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:27.214465Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:28.553536Z | Info | Live bytes: 774.58MB Heap size: 2422.21MB +2024-07-24T09:40:28.759551Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:29.293447Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:29.792011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:30.343112Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:30.867517Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:31.569885Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:31.849514Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:31.965410Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:40:32.102904Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:32.780588Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:33.347712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:36.649975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:37.277914Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:38.037675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:40:58.231727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:00.194379Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:01.082995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:03.287809Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:03.481468Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:41:04.107229Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:10.466265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:10.968822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:12.699947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:28.565512Z | Info | Live bytes: 788.96MB Heap size: 2422.21MB +2024-07-24T09:41:43.523832Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:41:44.389317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:14.676294Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:14.786625Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:42:15.219762Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:16.253349Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:21.331662Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:24.348426Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:25.118288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:25.909822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:28.569491Z | Info | Live bytes: 804.36MB Heap size: 2422.21MB +2024-07-24T09:42:35.747564Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:39.904655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:40.547998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:42:40.748357Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:42:46.708932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:43:28.607474Z | Info | Live bytes: 817.85MB Heap size: 2422.21MB +2024-07-24T09:44:06.901211Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:07.438597Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:08.042152Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:08.624145Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:09.550097Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:15.843043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:20.568619Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:20.832000Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:44:21.089649Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:21.648140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:25.485218Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:26.586033Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:27.199683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:27.971913Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:28.608944Z | Info | Live bytes: 829.24MB Heap size: 2422.21MB +2024-07-24T09:44:28.650567Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:29.200226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:33.879572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:38.243896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:39.990721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:41.128992Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:42.524705Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:44.082127Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:48.956324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:51.520998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:54.279304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:57.443221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:58.585272Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:58.809712Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:44:59.253663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:44:59.936739Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:00.132543Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:10.904793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:14.881384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:17.149352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:17.212439Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:17.329927Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:17.433948Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:17.507574Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:17.644937Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:19.101812Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:20.365667Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:20.917906Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:22.090300Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:22.813685Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:23.477828Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:23.845334Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:23.965733Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:24.090997Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:24.767763Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:25.079065Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:25.180730Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:25.552886Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:25.630264Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:25.658846Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:25.783728Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:26.226697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:26.925573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:26.988283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:27.410088Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:27.859921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:27.900336Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:27.977390Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:28.114416Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:28.412510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:28.610490Z | Info | Live bytes: 861.24MB Heap size: 2422.21MB +2024-07-24T09:45:29.039058Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:29.112091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:29.127950Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:29.761423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:29.804313Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:29.876842Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:30.318826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:31.103659Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:36.420947Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:37.746636Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:37.809647Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:38.111320Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:38.205717Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:39.256321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:39.322623Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:45:39.995407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:50.701721Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:50.905590Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:45:53.515824Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:54.227894Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:54.343814Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:54.413557Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:54.557660Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:55.467679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:56.010026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:57.239479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:57.733842Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:58.898048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:45:59.070723Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:45:59.465581Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:00.116872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:01.073026Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:01.689470Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:01.748677Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:03.508867Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:06.464312Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:06.589563Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:07.043475Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:07.181666Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:07.289966Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:07.413982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:07.619041Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:08.650705Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:08.712420Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:08.894823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:12.588064Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:13.118268Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:13.985847Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:14.595495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:15.249996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:15.744108Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:16.348165Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:16.892405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:17.458355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:18.708284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:19.273880Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:19.278477Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:46:19.808324Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:20.339333Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:23.008225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:25.805640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:28.614503Z | Info | Live bytes: 1013.63MB Heap size: 2422.21MB +2024-07-24T09:46:29.374822Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:46:32.904086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:47:28.631903Z | Info | Live bytes: 1013.63MB Heap size: 2422.21MB +2024-07-24T09:48:28.692387Z | Info | Live bytes: 1013.63MB Heap size: 2422.21MB +2024-07-24T09:49:28.752566Z | Info | Live bytes: 1013.63MB Heap size: 2422.21MB +2024-07-24T09:49:54.722928Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:49:55.516754Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:49:57.888054Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:49:58.708702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:50:01.778877Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:50:02.824479Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:50:05.279066Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:50:06.899160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:50:14.422134Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:50:28.763493Z | Info | Live bytes: 1021.66MB Heap size: 2433.74MB +2024-07-24T09:51:28.823332Z | Info | Live bytes: 1021.66MB Heap size: 2433.74MB +2024-07-24T09:51:33.506163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:34.005550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:34.524345Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:35.053286Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:35.557121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:36.083219Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:36.685600Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:37.236321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:38.427003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:39.396853Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:39.901736Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:40.413181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:51:42.393502Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:52:28.870350Z | Info | Live bytes: 1081.32MB Heap size: 2494.56MB +2024-07-24T09:53:02.717069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:03.388980Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:28.875294Z | Info | Live bytes: 1081.32MB Heap size: 2494.56MB +2024-07-24T09:53:33.362823Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:36.654924Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:37.184226Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:37.896864Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:53:38.236147Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:39.364443Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:53:39.814895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:42.264042Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:42.824770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:45.013157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:45.198204Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:53:45.550227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:46.091187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:48.998130Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:50.143414Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:51.495850Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:53:53.383261Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:01.113364Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:01.967104Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:03.233021Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:06.482153Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:54:07.106932Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:12.862419Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:13.401936Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:14.169442Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:14.705058Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:15.598350Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:21.539408Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:23.174582Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:23.721770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:24.219043Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:25.147086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:27.070278Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:27.591622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:28.286710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:28.835991Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:54:28.876334Z | Info | Live bytes: 625.70MB Heap size: 2853.18MB +2024-07-24T09:54:42.819061Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:43.046106Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:54:43.389746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:46.367548Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:54:46.766119Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:54:46.803679Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:50.132160Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:50.655591Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:51.437011Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:54:56.833526Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:04.997890Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:05.127495Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:05.402804Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:05.665330Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:05.869425Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:06.072819Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:06.117601Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:07.176073Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:07.319970Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:07.618897Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:08.531793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:28.897505Z | Info | Live bytes: 641.80MB Heap size: 2853.18MB +2024-07-24T09:55:29.718390Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:29.865684Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:30.246908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:34.556702Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:38.693688Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:38.708382Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:39.514395Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:40.114369Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:40.451983Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:41.312840Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:41.474698Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:55:41.827503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:55:42.519702Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:56:28.944418Z | Info | Live bytes: 653.26MB Heap size: 2853.18MB +2024-07-24T09:57:00.224769Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:00.305372Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:00.521435Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:00.553628Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:01.223473Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:01.305391Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:01.320315Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:01.549525Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:01.641048Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:01.693523Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:02.002072Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:02.952007Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:03.053609Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:03.153860Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:03.244545Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:03.452910Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:03.509252Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:28.964523Z | Info | Live bytes: 670.20MB Heap size: 2853.18MB +2024-07-24T09:57:54.293448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:54.786076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:57.653357Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T09:57:57.965615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:58.488563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:59.079615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:57:59.703846Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:58:11.356783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:58:28.978454Z | Info | Live bytes: 691.24MB Heap size: 2853.18MB +2024-07-24T09:58:38.850916Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T09:58:39.355133Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Protocol/AvailableEras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs" ] +2024-07-24T09:59:29.028409Z | Info | Live bytes: 691.24MB Heap size: 2853.18MB +2024-07-24T10:00:12.079339Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:00:16.595220Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:00:19.525964Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:00:29.033342Z | Info | Live bytes: 709.79MB Heap size: 2853.18MB +2024-07-24T10:00:36.894967Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:00:37.616837Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:01:29.084374Z | Info | Live bytes: 718.40MB Heap size: 2853.18MB +2024-07-24T10:02:05.246855Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:02:06.584813Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:02:06.636398Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:02:29.098754Z | Info | Live bytes: 718.40MB Heap size: 2853.18MB +2024-07-24T10:03:29.153396Z | Info | Live bytes: 718.40MB Heap size: 2853.18MB +2024-07-24T10:04:29.213503Z | Info | Live bytes: 718.40MB Heap size: 2853.18MB +2024-07-24T10:05:29.253324Z | Info | Live bytes: 718.40MB Heap size: 2853.18MB +2024-07-24T10:06:29.275255Z | Info | Live bytes: 718.40MB Heap size: 2853.18MB +2024-07-24T10:07:29.335315Z | Info | Live bytes: 718.40MB Heap size: 2853.18MB +2024-07-24T10:07:29.923048Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:07:30.410857Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:08:29.391415Z | Info | Live bytes: 766.03MB Heap size: 2853.18MB +2024-07-24T10:08:51.018283Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:08:51.977768Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:08:54.181343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:08:55.514789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:09:16.306060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:09:29.423529Z | Info | Live bytes: 777.04MB Heap size: 2853.18MB +2024-07-24T10:10:14.969981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:10:15.612306Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:10:16.343664Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:10:16.466140Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:10:16.691877Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:10:17.014157Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:10:18.055120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:10:19.140187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:10:19.992284Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:10:29.428348Z | Info | Live bytes: 894.10MB Heap size: 2853.18MB +2024-07-24T10:11:29.488740Z | Info | Live bytes: 894.10MB Heap size: 2853.18MB +2024-07-24T10:11:42.227234Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:43.417833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:44.448046Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:11:44.819182Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:45.412038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:46.101504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:46.647786Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:47.210975Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:48.898321Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:49.402107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:50.204111Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:50.819017Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:51.560105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:52.090293Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:52.642110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:53.278022Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:53.830086Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:54.388949Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:55.125626Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:56.325585Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:56.756958Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:11:56.858470Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:56.999711Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:11:57.370908Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:58.379135Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:58.913404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:11:59.888790Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:00.386001Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:01.071838Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:01.587310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:02.849632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:03.424423Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:03.958410Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:04.587869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:05.225895Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:05.935151Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:06.788749Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:07.452282Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:07.555394Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:08.123316Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:10.030143Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:10.740692Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:11.314037Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:12.248854Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:12.415077Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:12.788265Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:13.366463Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:14.072784Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:15.031107Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:17.505758Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:17.856120Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:18.147002Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:18.246428Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:18.290756Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:19.650164Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:20.252354Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:21.602146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:22.217443Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:23.273954Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:24.320191Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:24.554515Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:24.863965Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:25.491212Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:26.178852Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:26.264747Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:27.358893Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:28.076935Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:29.491366Z | Info | Live bytes: 1081.39MB Heap size: 2927.62MB +2024-07-24T10:12:32.650007Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:32.778789Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:33.048865Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:33.329917Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:33.382229Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:33.613113Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:33.734468Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:33.849833Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:34.000503Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:34.399522Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:34.482050Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:34.802723Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:35.399615Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:35.893886Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:36.766158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:37.450501Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:37.488625Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:37.535782Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:37.647526Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:37.836188Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:38.013138Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:38.073177Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:38.296573Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:38.680870Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:38.690436Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:39.223502Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:39.535563Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:40.155000Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:40.474675Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:40.615160Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:12:41.008319Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:41.931979Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:42.788102Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:43.675782Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:44.995669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:12:46.507718Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:13:29.525414Z | Info | Live bytes: 717.75MB Heap size: 3037.72MB +2024-07-24T10:13:41.660746Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:13:41.746982Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-07-24T10:13:43.867905Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:13:44.467785Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:13:58.942655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:13:59.676087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T10:14:29.551371Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:15:29.583361Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:16:29.643338Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:17:29.656538Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:18:29.716877Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:19:29.777258Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:20:29.837654Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:21:29.851498Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:22:29.911890Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:23:29.972305Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:24:29.992556Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:25:30.024547Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:26:30.084953Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:27:30.097318Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:28:30.157983Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:29:30.218705Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:30:30.279219Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:31:30.325364Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:32:30.385792Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:33:30.446378Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:34:30.464605Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:35:30.472594Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:36:30.533106Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:37:30.536632Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:38:30.596979Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:39:30.657413Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:40:30.718092Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:41:30.778685Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:42:30.808631Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:43:30.856578Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:44:30.917228Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:45:30.938312Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:46:30.973135Z | Info | Live bytes: 845.82MB Heap size: 3037.72MB +2024-07-24T10:47:26.084522Z | Info | LSP: received shutdown +2024-07-24T10:47:26.092502Z | Error | Got EOF +2024-07-24 16:26:44.1420000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-24 16:26:44.1430000 [client] INFO Finding haskell-language-server +2024-07-24 16:26:44.1440000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:44.1450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:44.1510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-24 16:26:44.4530000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:44.4530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:44.4590000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-24 16:26:44.6250000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:44.6260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:44.6320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-24 16:26:44.8090000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:44.8090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:44.8170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-24 16:26:44.9700000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:44.9700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:44.9770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-24 16:26:44.9950000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:44.9950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:45.0030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-24 16:26:45.0200000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:45.0200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:45.0270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-24 16:26:45.0500000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-24 16:26:45.1010000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:45.1020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:45.1110000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-24 16:26:45.2380000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-24 16:26:45.2390000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-24 16:26:56.5760000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-07-24 16:26:56.7040000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-24 16:26:56.7040000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:56.7040000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:56.7120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-24 16:26:56.8380000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:56.8380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:56.8470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-24 16:26:56.8650000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:56.8650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:56.8700000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-24 16:26:56.8850000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:56.8860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:56.8920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-07-24 16:26:56.9100000 [client] INFO Checking for ghcup installation +2024-07-24 16:26:56.9100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 16:26:56.9160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-07-24 16:26:57.0520000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-24 16:26:57.0520000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-24 16:26:57.0520000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-24 16:26:57.0520000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-24 16:26:57.0520000 [client] INFO server environment variables: +2024-07-24 16:26:57.0520000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-24 16:26:57.0530000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-24 16:26:57.0530000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-24 16:26:57.0540000 [client] INFO Starting language server +2024-07-24T16:27:07.399851Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-07-24T16:27:07.400638Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-24T16:27:07.400878Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T16:27:07.403420Z | Info | Logging heap statistics every 60.00s +2024-07-24T16:27:07.413740Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T16:27:07.414153Z | Info | Starting server +2024-07-24T16:27:07.415710Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-24T16:27:07.466606Z | Info | Started LSP server in 0.05s +2024-07-24T16:27:09.149627Z | Info | Cradle path: cardano-api/internal/Cardano/Api/ProtocolParameters.hs +2024-07-24T16:27:09.150283Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-24T16:27:09.552441Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T16:27:10.981038Z | Info | Load cabal cradle using single file +2024-07-24T16:27:12.245130Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT939979-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-07-24T16:27:16.836142Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-38b619f1c9b7be1ee3848670d3bd96b585a13082 +2024-07-24T16:27:16.841593Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-24T16:28:07.350616Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T16:28:07.405174Z | Info | Live bytes: 551.32MB Heap size: 2038.43MB +2024-07-24T16:28:11.115598Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T16:28:32.824574Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-07-24T16:28:32.825108Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-24T16:28:32.871834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T16:28:34.766069Z | Info | Load cabal cradle using single file +2024-07-24T16:28:35.929339Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT939979-4 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-07-24T16:28:39.403384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T16:29:07.439500Z | Info | Live bytes: 650.26MB Heap size: 2038.43MB +2024-07-24T16:30:07.444496Z | Info | Live bytes: 649.75MB Heap size: 2038.43MB +2024-07-24T16:30:09.580119Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T16:31:07.501978Z | Info | Live bytes: 662.60MB Heap size: 2038.43MB +2024-07-24T16:32:07.561338Z | Info | Live bytes: 662.60MB Heap size: 2038.43MB +2024-07-24T16:32:45.403181Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-24T16:33:07.567337Z | Info | Live bytes: 672.12MB Heap size: 2038.43MB +2024-07-24T16:34:07.627384Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:35:07.675240Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:36:07.735525Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:37:07.795490Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:38:07.855596Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:39:07.915590Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:40:07.975446Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:41:08.035836Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:42:08.095416Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:43:08.156313Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:44:08.216432Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:45:08.276544Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:46:08.289537Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:47:08.349548Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:48:08.409333Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:49:08.467775Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:50:08.506209Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:51:08.566472Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:52:08.626412Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:53:08.686385Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:54:08.746933Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:55:08.807545Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:56:08.867557Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:57:08.927419Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:58:08.952434Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T16:59:09.012438Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:00:09.070457Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:01:09.130517Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:02:09.190434Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:03:09.250883Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:04:09.311289Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:05:09.371430Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:06:09.431381Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:07:09.480594Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:08:09.529784Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:09:09.590224Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:10:09.650850Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:11:09.689505Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:12:09.750017Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:13:09.810449Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:14:09.818879Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:15:09.879396Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:16:09.882774Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:17:09.896189Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:18:09.909622Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:19:09.970115Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:20:10.030595Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:21:10.090633Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:22:10.151114Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:23:10.211669Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:24:10.272179Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:25:10.283619Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:26:10.344129Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:27:10.388517Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:28:10.448996Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:29:10.509538Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:30:10.570061Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:31:10.630393Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:32:10.637626Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:33:10.664559Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:34:10.725065Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:35:10.785471Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:36:10.845963Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:37:10.906482Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:38:10.910843Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:39:10.970931Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:40:11.031547Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:41:11.091507Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:42:11.097912Z | Info | Live bytes: 689.62MB Heap size: 2038.43MB +2024-07-24T17:43:00.234330Z | Info | LSP: received shutdown +2024-07-24T17:43:00.236472Z | Error | Got EOF +2024-07-24 21:04:07.7410000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-24 21:04:07.7420000 [client] INFO Finding haskell-language-server +2024-07-24 21:04:07.7440000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:07.7440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:07.7510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-24 21:04:08.1040000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:08.1050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:08.1090000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-24 21:04:08.2430000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:08.2440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:08.2490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-24 21:04:08.3950000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:08.3950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:08.4010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-24 21:04:08.5230000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:08.5230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:08.5280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-24 21:04:08.5420000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:08.5430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:08.5480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-24 21:04:08.5650000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:08.5650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:08.5720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-24 21:04:08.5930000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-24 21:04:08.6360000 [client] INFO Checking for ghcup installation +2024-07-24 21:04:08.6360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:04:08.6430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-24 21:04:08.7820000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-24 21:04:08.7820000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-24 21:17:47.4790000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-24 21:17:47.4810000 [client] INFO Finding haskell-language-server +2024-07-24 21:17:47.4820000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:47.4820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:47.4910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-24 21:17:47.8240000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:47.8240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:47.8290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-24 21:17:48.0150000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:48.0150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:48.0220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-24 21:17:48.1570000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:48.1570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:48.1620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-24 21:17:48.3010000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:48.3010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:48.3070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-24 21:17:48.3220000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:48.3220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:48.3270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-24 21:17:48.3420000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:48.3420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:48.3470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-24 21:17:48.3660000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-24 21:17:48.4010000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:48.4010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:48.4070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-24 21:17:48.5220000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-24 21:17:48.5230000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-24 21:17:50.3680000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-07-24 21:17:50.4790000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-24 21:17:50.4790000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:50.4790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:50.4830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-24 21:17:50.5790000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:50.5790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:50.5850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-24 21:17:50.6050000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:50.6050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:50.6100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-24 21:17:50.6240000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:50.6240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:50.6290000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-07-24 21:17:50.6430000 [client] INFO Checking for ghcup installation +2024-07-24 21:17:50.6430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-24 21:17:50.6470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-07-24 21:17:50.7530000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-24 21:17:50.7540000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-24 21:17:50.7540000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-24 21:17:50.7540000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-24 21:17:50.7540000 [client] INFO server environment variables: +2024-07-24 21:17:50.7540000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-24 21:17:50.7540000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-24 21:17:50.7540000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-24 21:17:50.7550000 [client] INFO Starting language server +2024-07-24T21:17:59.301230Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-07-24T21:17:59.302077Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-24T21:17:59.302253Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T21:17:59.304288Z | Info | Logging heap statistics every 60.00s +2024-07-24T21:17:59.311487Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-24T21:17:59.311800Z | Info | Starting server +2024-07-24T21:17:59.313536Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-24T21:17:59.350123Z | Info | Started LSP server in 0.04s +2024-07-24T21:18:00.577164Z | Info | LSP: received shutdown +2024-07-24T21:18:00.577992Z | Info | Reactor thread stopped +2024-07-24T21:18:00.585592Z | Error | Got EOF +2024-07-25 05:49:06.6310000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-25 05:49:06.6330000 [client] INFO Finding haskell-language-server +2024-07-25 05:49:06.6360000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:06.6360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:06.6450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-25 05:49:06.8440000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:06.8440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:06.8490000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-25 05:49:07.0850000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:07.0850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:07.0930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-25 05:49:07.3120000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:07.3120000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:07.3160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-25 05:49:07.5320000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:07.5320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:07.5390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-25 05:49:07.5580000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:07.5580000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:07.5650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-25 05:49:07.5860000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:07.5860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:07.5940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-25 05:49:07.6140000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-25 05:49:07.7530000 [client] INFO Checking for ghcup installation +2024-07-25 05:49:07.7530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 05:49:07.7600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-25 05:49:07.9280000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-25 05:49:07.9280000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-25 10:16:46.2360000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-25 10:16:46.2370000 [client] INFO Finding haskell-language-server +2024-07-25 10:16:46.2380000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:46.2390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:46.2450000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-25 10:16:46.5300000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:46.5300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:46.5340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-25 10:16:46.6500000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:46.6500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:46.6570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-25 10:16:46.8220000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:46.8220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:46.8270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-25 10:16:46.9540000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:46.9540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:46.9590000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-25 10:16:46.9780000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:46.9780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:46.9830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-25 10:16:47.0030000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:47.0030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:47.0080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-25 10:16:47.0330000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-25 10:16:47.0640000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:47.0640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:47.0700000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-25 10:16:47.1770000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-25 10:16:47.1770000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-25 10:16:56.8310000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-07-25 10:16:56.9680000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-25 10:16:56.9690000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:56.9690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:56.9730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-25 10:16:57.0580000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:57.0580000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:57.0620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-25 10:16:57.0790000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:57.0790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:57.0840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-25 10:16:57.0980000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:57.0980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:57.1020000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-07-25 10:16:57.1160000 [client] INFO Checking for ghcup installation +2024-07-25 10:16:57.1160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-25 10:16:57.1210000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-07-25 10:16:57.2260000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-25 10:16:57.2270000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-25 10:16:57.2270000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-25 10:16:57.2270000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-25 10:16:57.2270000 [client] INFO server environment variables: +2024-07-25 10:16:57.2270000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-25 10:16:57.2270000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-25 10:16:57.2270000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-25 10:16:57.2280000 [client] INFO Starting language server +2024-07-25T10:17:06.003247Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-07-25T10:17:06.003992Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-25T10:17:06.004220Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-25T10:17:06.006500Z | Info | Logging heap statistics every 60.00s +2024-07-25T10:17:06.014298Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-25T10:17:06.014754Z | Info | Starting server +2024-07-25T10:17:06.016651Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-25T10:17:06.092318Z | Info | Started LSP server in 0.08s +2024-07-25T10:17:07.338513Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-07-25T10:17:07.339422Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-25T10:17:07.832805Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-25T10:17:08.842878Z | Info | Load cabal cradle using single file +2024-07-25T10:17:09.842043Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT106886-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-07-25T10:17:13.630370Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-38b619f1c9b7be1ee3848670d3bd96b585a13082 +2024-07-25T10:17:13.635857Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-25T10:18:06.034700Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:19:06.095298Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:20:06.155553Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:21:06.215677Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:22:06.276241Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:23:06.321588Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:24:06.382283Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:25:06.442598Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:26:06.455691Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:27:06.494455Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:28:06.526700Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:29:06.586511Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:30:06.643038Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:31:06.678640Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:32:06.739296Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:33:06.750493Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:34:06.810934Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:35:06.871408Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:36:06.890797Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:37:06.947156Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:38:07.007601Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:39:07.067534Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:40:07.127391Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:41:07.134607Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:42:07.150511Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:43:07.196158Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:44:07.213572Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:45:07.274073Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:46:07.294592Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:47:07.347922Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:48:07.408437Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:49:07.429839Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:50:07.490285Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:51:07.546887Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:52:07.606404Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:53:07.646629Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:54:07.651714Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:55:07.659686Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:56:07.663465Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:57:07.704129Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:58:07.764413Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T10:59:07.825093Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:00:07.885837Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:01:07.902647Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:02:07.905630Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:03:07.923348Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:04:07.983909Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:05:08.044558Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:06:08.100684Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:07:08.161341Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:08:08.221987Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:09:08.254665Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:10:08.278675Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:11:08.338456Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:12:08.341562Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:13:08.402097Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:14:08.462430Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:15:08.523121Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:16:08.583886Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:17:08.644339Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:18:08.704511Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:19:08.765076Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:20:08.825463Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:21:08.885351Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:22:08.945523Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:23:08.990624Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:24:09.050383Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:25:09.101337Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:26:09.161390Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:27:09.221839Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:28:09.282068Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:29:09.342532Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:30:09.356618Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:31:09.416340Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:32:09.476599Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:33:09.537444Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:34:09.597526Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:35:09.658211Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:36:09.700163Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:37:09.726523Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:38:09.777640Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:39:09.838234Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:40:09.870638Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:41:09.887858Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:42:09.935964Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:43:09.996477Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:44:10.057133Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:45:10.092120Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:46:10.102398Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:47:10.162509Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:48:10.197114Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:49:10.250244Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:50:10.310514Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:51:10.371247Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:52:10.386105Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:53:10.416856Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:54:10.476367Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:55:10.500156Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:56:10.522625Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:57:10.583374Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:58:10.643349Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T11:59:10.668641Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:00:10.702618Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:01:10.762550Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:02:10.823096Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:03:10.883516Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:04:10.944128Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:05:10.980677Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:06:11.020608Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:07:11.081226Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:08:11.142065Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:09:11.201478Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:10:11.261345Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:11:11.321558Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:12:11.381483Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:13:11.430500Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:14:11.491043Z | Info | Live bytes: 371.79MB Heap size: 1629.49MB +2024-07-25T12:14:46.400171Z | Info | LSP: received shutdown +2024-07-25T12:14:46.402429Z | Info | Reactor thread stopped +2024-07-25T12:14:46.402821Z | Error | Got EOF +2024-07-26 11:07:37.9540000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-26 11:07:37.9550000 [client] INFO Finding haskell-language-server +2024-07-26 11:07:37.9550000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:37.9560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:37.9610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-26 11:07:38.4950000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:38.4960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:38.5030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-26 11:07:38.6390000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:38.6390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:38.6440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-26 11:07:38.8010000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:38.8020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:38.8080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-26 11:07:38.9580000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:38.9580000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:38.9620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-26 11:07:38.9750000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:38.9750000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:38.9800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-26 11:07:38.9930000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:38.9930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:38.9980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-26 11:07:39.0180000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-26 11:07:39.0460000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:39.0460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:39.0530000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-26 11:07:39.1590000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-26 11:07:39.1590000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-26 11:07:45.6870000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-07-26 11:07:45.9910000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-26 11:07:45.9920000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:45.9920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:45.9960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-26 11:07:46.0910000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:46.0910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:46.0960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-26 11:07:46.1130000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:46.1130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:46.1190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-26 11:07:46.1340000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:46.1340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:46.1400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-07-26 11:07:46.1550000 [client] INFO Checking for ghcup installation +2024-07-26 11:07:46.1550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-26 11:07:46.1610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-07-26 11:07:46.2660000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-26 11:07:46.2670000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-26 11:07:46.2670000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-26 11:07:46.2670000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-26 11:07:46.2670000 [client] INFO server environment variables: +2024-07-26 11:07:46.2670000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-26 11:07:46.2670000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-26 11:07:46.2670000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-26 11:07:46.2680000 [client] INFO Starting language server +2024-07-26T11:07:56.032730Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-07-26T11:07:56.034702Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-26T11:07:56.035335Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-26T11:07:56.038770Z | Info | Logging heap statistics every 60.00s +2024-07-26T11:07:56.047793Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-26T11:07:56.048460Z | Info | Starting server +2024-07-26T11:07:56.050580Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-26T11:07:56.103484Z | Info | Started LSP server in 0.06s +2024-07-26T11:07:58.139434Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-07-26T11:07:58.140328Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-26T11:07:58.650791Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-26T11:08:00.135107Z | Info | Load cabal cradle using single file +2024-07-26T11:08:01.276309Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT59581-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-07-26T11:08:05.660634Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-38b619f1c9b7be1ee3848670d3bd96b585a13082 +2024-07-26T11:08:05.666218Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-26T11:08:33.758330Z | Info | LSP: received shutdown +2024-07-26T11:08:33.759917Z | Error | Got EOF +2024-07-27 08:55:06.3210000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-27 08:55:06.3230000 [client] INFO Finding haskell-language-server +2024-07-27 08:55:06.3250000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:06.3250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:06.3300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-27 08:55:06.5710000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:06.5720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:06.5760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-27 08:55:06.6990000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:06.6990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:06.7030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-27 08:55:06.8090000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:06.8090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:06.8140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-27 08:55:06.9230000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:06.9230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:06.9270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-27 08:55:06.9410000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:06.9410000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:06.9460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-27 08:55:06.9610000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:06.9610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:06.9660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-27 08:55:06.9880000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-27 08:55:07.0280000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:07.0280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:07.0330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-27 08:55:07.1380000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-27 08:55:07.1390000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-27 08:55:12.7560000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-07-27 08:55:12.9120000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-27 08:55:12.9130000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:12.9130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:12.9170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-27 08:55:12.9910000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:12.9910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:12.9950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-27 08:55:13.0130000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:13.0130000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:13.0160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-27 08:55:13.0300000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:13.0300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:13.0330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-07-27 08:55:13.0460000 [client] INFO Checking for ghcup installation +2024-07-27 08:55:13.0470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 08:55:13.0500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-07-27 08:55:13.1440000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-27 08:55:13.1450000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-27 08:55:13.1450000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-27 08:55:13.1450000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-27 08:55:13.1450000 [client] INFO server environment variables: +2024-07-27 08:55:13.1450000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-27 08:55:13.1450000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-27 08:55:13.1450000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-27 08:55:13.1460000 [client] INFO Starting language server +2024-07-27T08:55:21.706775Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-07-27T08:55:21.709203Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-27T08:55:21.709681Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-27T08:55:21.715483Z | Info | Logging heap statistics every 60.00s +2024-07-27T08:55:21.727280Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-27T08:55:21.727742Z | Info | Starting server +2024-07-27T08:55:21.742549Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-27T08:55:21.806529Z | Info | Started LSP server in 0.08s +2024-07-27T08:55:23.145380Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Sign.hs +2024-07-27T08:55:23.146390Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-27T08:55:23.643142Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T08:55:24.463416Z | Info | Load cabal cradle using single file +2024-07-27T08:55:25.332586Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT31841-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-07-27T08:55:28.576507Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-38b619f1c9b7be1ee3848670d3bd96b585a13082 +2024-07-27T08:55:28.580573Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-27T08:56:21.732520Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T08:57:21.761248Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T08:58:21.821638Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T08:59:21.864295Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:00:21.873250Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:01:21.905280Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:02:21.965833Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:03:22.026397Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:04:22.027862Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:05:22.035747Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:06:22.036829Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:07:22.097344Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:08:22.158154Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:09:22.218904Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:10:22.279650Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:11:22.289296Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:12:22.293383Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:13:22.334720Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:14:22.369284Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:15:22.411252Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:16:22.471160Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:17:22.531693Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:18:22.558718Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:19:22.617082Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:20:22.677632Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:21:22.738168Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:22:22.780885Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:23:22.841133Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:24:22.855112Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:25:22.923084Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:26:22.983041Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:27:23.043152Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:28:23.103125Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:29:23.168062Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:30:23.201348Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:31:23.261028Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:32:23.263159Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:33:23.323877Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:34:23.384501Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:35:23.397490Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:36:23.457954Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:37:23.518089Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:38:23.578165Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:39:23.638920Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:40:23.645240Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:41:23.705819Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:42:23.766264Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:43:23.802648Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:44:23.844000Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:45:23.904583Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:46:23.965221Z | Info | Live bytes: 369.73MB Heap size: 1600.13MB +2024-07-27T09:46:50.640740Z | Info | LSP: received shutdown +2024-07-27T09:46:50.642405Z | Info | Reactor thread stopped +2024-07-27T09:46:50.642762Z | Error | Got EOF +2024-07-27 10:09:35.6080000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-07-27 10:09:35.6090000 [client] INFO Finding haskell-language-server +2024-07-27 10:09:35.6100000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:35.6100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:35.6170000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-07-27 10:09:35.8630000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:35.8640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:35.8710000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-27 10:09:35.9880000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:35.9880000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:35.9950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-07-27 10:09:36.1130000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:36.1140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:36.1190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-07-27 10:09:36.2380000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:36.2380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:36.2440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-27 10:09:36.2620000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:36.2630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:36.2690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-07-27 10:09:36.2830000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:36.2830000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:36.2880000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-07-27 10:09:36.3080000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-07-27 10:09:36.3510000 [client] INFO Checking for ghcup installation +2024-07-27 10:09:36.3510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:09:36.3560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-07-27 10:09:36.4930000 [client] INFO Working out the project GHC version. This might take a while... +2024-07-27 10:09:36.4940000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-07-27 10:10:06.4770000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-07-27 10:10:06.5520000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-07-27 10:10:06.5520000 [client] INFO Checking for ghcup installation +2024-07-27 10:10:06.5530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:10:06.5600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-07-27 10:10:06.6780000 [client] INFO Checking for ghcup installation +2024-07-27 10:10:06.6780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:10:06.6860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-07-27 10:10:06.7070000 [client] INFO Checking for ghcup installation +2024-07-27 10:10:06.7070000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:10:06.7150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-07-27 10:10:06.7320000 [client] INFO Checking for ghcup installation +2024-07-27 10:10:06.7320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:10:06.7380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-07-27 10:10:06.7550000 [client] INFO Checking for ghcup installation +2024-07-27 10:10:06.7550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-07-27 10:10:06.7630000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-07-27 10:10:06.9120000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-07-27 10:10:06.9130000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-27 10:10:06.9130000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-07-27 10:10:06.9130000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-27 10:10:06.9130000 [client] INFO server environment variables: +2024-07-27 10:10:06.9130000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-07-27 10:10:06.9140000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-07-27 10:10:06.9140000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-07-27 10:10:06.9160000 [client] INFO Starting language server +2024-07-27T10:10:18.544112Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-07-27T10:10:18.545622Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-07-27T10:10:18.546044Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-27T10:10:18.549755Z | Info | Logging heap statistics every 60.00s +2024-07-27T10:10:18.557290Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-07-27T10:10:18.557781Z | Info | Starting server +2024-07-27T10:10:18.560863Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-07-27T10:10:18.643926Z | Info | Started LSP server in 0.09s +2024-07-27T10:10:20.094454Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Sign.hs +2024-07-27T10:10:20.095508Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-07-27T10:10:20.599710Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T10:10:21.785366Z | Info | Load cabal cradle using single file +2024-07-27T10:10:22.812463Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT154726-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-07-27T10:10:26.584257Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-4680c848285cdcb20b8c192b1586026351591b55 +2024-07-27T10:10:26.588299Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-07-27T10:11:18.599369Z | Info | Live bytes: 336.09MB Heap size: 1668.28MB +2024-07-27T10:11:45.756684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T10:12:18.630101Z | Info | Live bytes: 387.90MB Heap size: 1668.28MB +2024-07-27T10:12:22.052244Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T10:13:18.678133Z | Info | Live bytes: 413.80MB Heap size: 1668.28MB +2024-07-27T10:14:07.193748Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T10:14:18.680643Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:15:18.727612Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:16:18.784101Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:17:18.844972Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:18:18.905140Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:19:18.955184Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:20:19.015276Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:21:19.075110Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:22:19.108314Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:23:19.117942Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:49:25.414190Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:50:25.428122Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:51:25.438088Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:52:25.498305Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:53:25.558439Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:54:25.618198Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:55:25.678287Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:56:25.722787Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:57:25.773834Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:58:25.834645Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T10:59:25.855700Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:00:25.900249Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:01:25.960902Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:02:26.021630Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:03:26.024449Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:04:26.068709Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:05:26.129186Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:06:26.155556Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:07:26.216198Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:08:26.236401Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:09:26.251161Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:10:26.259141Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:11:26.319718Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:12:26.380209Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:13:26.398624Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:14:26.441590Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:15:26.460804Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:16:26.521373Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:17:26.580417Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:18:26.614272Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:19:26.674250Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:20:26.734597Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:21:26.744329Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:22:26.804759Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:23:26.817432Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:24:26.854578Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:25:26.911071Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:26:26.971310Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:27:27.031667Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:28:27.091549Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:29:27.100573Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:30:27.142800Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:31:27.203247Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:32:27.243284Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:33:27.259705Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:34:27.293286Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:35:27.343283Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:36:27.351298Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:37:27.379762Z | Info | Live bytes: 391.88MB Heap size: 2008.02MB +2024-07-27T11:38:27.440717Z | Info | Live bytes: 401.05MB Heap size: 2008.02MB +2024-07-27T11:39:04.306189Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Body.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Query.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/IPC.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/InMode.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Poll.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Query.hs" ] +2024-07-27T11:39:27.458260Z | Info | Live bytes: 547.61MB Heap size: 2008.02MB +2024-07-27T11:40:27.489352Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:41:27.549918Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:42:27.600509Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:43:27.660236Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:44:27.720795Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:45:27.762128Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:46:27.822727Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:47:27.883345Z | Info | Live bytes: 547.59MB Heap size: 2008.02MB +2024-07-27T11:48:27.901598Z | Info | Live bytes: 554.84MB Heap size: 2008.02MB +2024-07-27T11:49:27.961280Z | Info | Live bytes: 555.43MB Heap size: 2008.02MB +2024-07-27T11:49:43.288703Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T11:50:28.001440Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:51:28.061343Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:52:28.121881Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:53:28.164710Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:54:28.166845Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:55:28.177023Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:56:28.237620Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:57:28.239012Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:58:28.291634Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T11:59:28.352268Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:00:28.371956Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:01:28.429202Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:02:28.476565Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:03:28.536218Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:04:28.596723Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:05:28.609399Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:06:28.649039Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:07:28.693137Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:08:28.726839Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:09:28.746163Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:10:28.761335Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:11:28.821853Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:12:28.828767Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:13:28.888158Z | Info | Live bytes: 572.56MB Heap size: 2008.02MB +2024-07-27T12:14:28.948644Z | Info | Live bytes: 585.49MB Heap size: 2008.02MB +2024-07-27T12:15:29.008351Z | Info | Live bytes: 585.49MB Heap size: 2008.02MB +2024-07-27T12:15:48.187493Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T12:16:04.922607Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T12:16:29.029738Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:17:29.068649Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:18:29.128162Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:19:29.188337Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:20:12.187310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T12:20:29.205447Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:21:29.261860Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:22:29.322346Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:23:29.382294Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:24:29.422484Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:25:29.482993Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:26:29.528178Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:27:29.559174Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:28:29.570487Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:29:29.630848Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:30:29.691306Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:31:29.702367Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:32:29.707295Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:33:29.739325Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:34:29.799865Z | Info | Live bytes: 583.57MB Heap size: 2008.02MB +2024-07-27T12:34:33.643288Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-07-27T12:35:29.802026Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:36:29.803207Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:37:29.831641Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:38:29.835636Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:39:29.839562Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:40:29.885695Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:41:29.945256Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:42:30.005769Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:43:30.061752Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:44:30.081433Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:45:30.141361Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:46:30.201267Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:47:30.261952Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:48:30.266988Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:49:30.327404Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:50:30.387840Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:51:30.396880Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:52:30.457392Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:53:30.518007Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:54:30.578434Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:55:30.614985Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:56:30.666598Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:57:30.727160Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:58:30.731029Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T12:59:30.742314Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:00:30.802285Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:01:30.853211Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:02:30.884380Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:03:30.944197Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:04:30.947392Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:05:31.007297Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:06:31.012891Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:07:31.072204Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:08:31.101603Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:09:31.161970Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:10:31.222431Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:11:31.282210Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:12:31.342160Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:13:31.402287Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:14:31.462278Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:15:31.522206Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:16:31.582273Z | Info | Live bytes: 597.93MB Heap size: 2008.02MB +2024-07-27T13:17:31.603407Z | Info | Live bytes: 603.40MB Heap size: 2008.02MB +2024-07-27T13:18:31.663482Z | Info | Live bytes: 603.40MB Heap size: 2008.02MB +2024-07-27T13:19:31.723171Z | Info | Live bytes: 603.40MB Heap size: 2008.02MB +2024-07-27T13:20:31.783289Z | Info | Live bytes: 603.40MB Heap size: 2008.02MB +2024-07-27T13:21:31.843730Z | Info | Live bytes: 603.40MB Heap size: 2008.02MB +2024-07-27T13:22:31.904286Z | Info | Live bytes: 603.40MB Heap size: 2008.02MB +2024-07-27T13:22:56.804424Z | Info | LSP: received shutdown +2024-07-27T13:22:56.807099Z | Info | Reactor thread stopped +2024-07-27T13:22:56.807885Z | Error | Got EOF +2024-08-06 12:08:03.3520000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-06 12:08:03.3620000 [client] INFO Finding haskell-language-server +2024-08-06 12:08:03.3630000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:03.3630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:03.3680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-06 12:08:03.5200000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:03.5200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:03.5260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-06 12:08:03.6680000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:03.6680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:03.6740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-06 12:08:03.7990000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:03.7990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:03.8060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-06 12:08:03.9150000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:03.9160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:03.9220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-06 12:08:03.9370000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:03.9370000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:03.9430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-06 12:08:03.9570000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:03.9570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:03.9620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-06 12:08:03.9800000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-06 12:08:04.0300000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:04.0300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:04.0360000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-06 12:08:04.1540000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-06 12:08:04.1550000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-06 12:08:14.1130000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-08-06 12:08:14.4350000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-06 12:08:14.4350000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:14.4350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:14.4380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-06 12:08:14.5220000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:14.5220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:14.5260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-06 12:08:14.5430000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:14.5430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:14.5470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-06 12:08:14.5600000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:14.5600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:14.5650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-08-06 12:08:14.5780000 [client] INFO Checking for ghcup installation +2024-08-06 12:08:14.5790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:08:14.5820000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-08-06 12:08:14.6660000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-06 12:08:14.6670000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-06 12:08:14.6670000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-06 12:08:14.6670000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-06 12:08:14.6670000 [client] INFO server environment variables: +2024-08-06 12:08:14.6670000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-06 12:08:14.6670000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-06 12:08:14.6670000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-06 12:08:14.6690000 [client] INFO Starting language server +2024-08-06T12:08:23.618777Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-08-06T12:08:23.619820Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-06T12:08:23.620193Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-06T12:08:23.623932Z | Info | Logging heap statistics every 60.00s +2024-08-06T12:08:23.631848Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-06T12:08:23.632220Z | Info | Starting server +2024-08-06T12:08:23.633706Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-06T12:08:23.687584Z | Info | Started LSP server in 0.06s +2024-08-06T12:08:24.983810Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-08-06T12:08:24.985082Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-06T12:08:25.547105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:08:26.426304Z | Info | Load cabal cradle using single file +2024-08-06T12:08:27.368895Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT21681-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-06T12:08:30.769747Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.0.0.0-inplace-internal-4680c848285cdcb20b8c192b1586026351591b55 +2024-08-06T12:08:30.775931Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.0.0.0-inplace-internal] +2024-08-06T12:09:23.661088Z | Info | Live bytes: 466.01MB Heap size: 1738.54MB +2024-08-06T12:10:23.721726Z | Info | Live bytes: 466.01MB Heap size: 1738.54MB +2024-08-06T12:11:23.752622Z | Info | Live bytes: 466.01MB Heap size: 1738.54MB +2024-08-06T12:11:26.314449Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:11:31.817519Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:11:33.602793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:12:23.790424Z | Info | Live bytes: 683.50MB Heap size: 2254.44MB +2024-08-06T12:12:26.638046Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:12:50.231231Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:12:54.211391Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:12:54.229045Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/ProposalProcedure.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/VotingProcedure.hs" ] +2024-08-06T12:12:54.562588Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/ProposalProcedure.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/VotingProcedure.hs" ] +2024-08-06T12:12:54.807942Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/ProposalProcedure.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/VotingProcedure.hs" ] +2024-08-06T12:12:55.117201Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-06T12:12:56.712447Z | Info | LSP: received shutdown +2024-08-06T12:12:56.714688Z | Error | Got EOF +2024-08-06 12:13:12.6190000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-06 12:13:12.6210000 [client] INFO Finding haskell-language-server +2024-08-06 12:13:12.6230000 [client] INFO Checking for ghcup installation +2024-08-06 12:13:12.6230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:13:12.6340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-06 12:13:13.2340000 [client] INFO Checking for ghcup installation +2024-08-06 12:13:13.2340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:13:13.2430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-06 12:13:13.5230000 [client] INFO Checking for ghcup installation +2024-08-06 12:13:13.5230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-06 12:13:13.5320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-07 15:29:30.6650000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-07 15:29:30.6670000 [client] INFO Finding haskell-language-server +2024-08-07 15:29:30.6680000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:30.6680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:30.6750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-07 15:29:30.8350000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:30.8350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:30.8410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-07 15:29:31.0090000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:31.0090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:31.0160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-07 15:29:31.1760000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:31.1760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:31.1840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-07 15:29:31.3260000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:31.3260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:31.3320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-07 15:29:31.3460000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:31.3460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:31.3520000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-07 15:29:31.3680000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:31.3680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:31.3750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-07 15:29:31.3970000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-07 15:29:31.4420000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:31.4420000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:31.4470000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-07 15:29:31.5630000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-07 15:29:31.5640000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-07 15:29:50.1720000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-08-07 15:29:50.4340000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-07 15:29:50.4340000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:50.4340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:50.4390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-07 15:29:50.5150000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:50.5150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:50.5190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-07 15:29:50.5360000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:50.5360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:50.5400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-07 15:29:50.5540000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:50.5540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:50.5580000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-08-07 15:29:50.5710000 [client] INFO Checking for ghcup installation +2024-08-07 15:29:50.5710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-07 15:29:50.5750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-08-07 15:29:50.6700000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-07 15:29:50.6700000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-07 15:29:50.6700000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-07 15:29:50.6700000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-07 15:29:50.6700000 [client] INFO server environment variables: +2024-08-07 15:29:50.6700000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-07 15:29:50.6700000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-07 15:29:50.6700000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-07 15:29:50.6710000 [client] INFO Starting language server +2024-08-07T15:30:16.616644Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-08-07T15:30:16.617777Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-07T15:30:16.617964Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-07T15:30:16.620163Z | Info | Logging heap statistics every 60.00s +2024-08-07T15:30:16.626984Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-07T15:30:16.627545Z | Info | Starting server +2024-08-07T15:30:16.628961Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-07T15:30:16.702335Z | Info | Started LSP server in 0.08s +2024-08-07T15:30:17.945278Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Governance/Actions/ProposalProcedure.hs +2024-08-07T15:30:17.946482Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-07T15:30:18.495572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:30:19.348681Z | Info | Load cabal cradle using single file +2024-08-07T15:30:20.275029Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT311363-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-07T15:30:29.166176Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-3eb22827ab0a27544f6d79a7b80afd417e6fbbbb +2024-08-07T15:30:29.174604Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.1.0.0-inplace-internal] +2024-08-07T15:30:32.422669Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:30:35.490378Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Governance/Actions/ProposalProcedure.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-08-07T15:30:53.650876Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:30:54.199720Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:30:54.753957Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:30:55.295622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:30:55.463192Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:30:55.965515Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:30:55.992575Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:30:56.508554Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:31:01.006003Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:31:01.765504Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:31:01.807901Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:31:16.626044Z | Info | Live bytes: 1913.29MB Heap size: 3199.21MB +2024-08-07T15:32:13.204415Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:32:13.747175Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:32:14.185330Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:32:14.703640Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:32:14.704355Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:32:15.036865Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:32:15.036865Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-07T15:32:16.626816Z | Info | Live bytes: 710.78MB Heap size: 3653.24MB +2024-08-07T15:32:31.708327Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:32:38.532783Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:33:16.663273Z | Info | Live bytes: 915.06MB Heap size: 3653.24MB +2024-08-07T15:34:16.724062Z | Info | Live bytes: 915.06MB Heap size: 3653.24MB +2024-08-07T15:35:16.734730Z | Info | Live bytes: 915.06MB Heap size: 3653.24MB +2024-08-07T15:36:16.794522Z | Info | Live bytes: 915.06MB Heap size: 3653.24MB +2024-08-07T15:37:16.830714Z | Info | Live bytes: 915.06MB Heap size: 3653.24MB +2024-08-07T15:38:16.853272Z | Info | Live bytes: 915.06MB Heap size: 3653.24MB +2024-08-07T15:38:21.914655Z | Info | Cradle path: cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs +2024-08-07T15:38:21.915338Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-07T15:38:21.955271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:38:23.616755Z | Info | Load cabal cradle using single file +2024-08-07T15:38:24.642963Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:gen + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT311363-189 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-07T15:39:16.907645Z | Info | Live bytes: 915.06MB Heap size: 3653.24MB +2024-08-07T15:39:20.593192Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:40:05.178246Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-gen-67a436b0889a38a9d53467b420d40c1c02825a04 +2024-08-07T15:40:05.178550Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-67a436b0889a38a9d53467b420d40c1c02825a04 +2024-08-07T15:40:05.184000Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.1.0.0-inplace-gen + , cardano-api-9.1.0.0-inplace-internal ] +2024-08-07T15:40:16.916513Z | Info | Live bytes: 1303.41MB Heap size: 3653.24MB +2024-08-07T15:41:16.976894Z | Info | Live bytes: 1303.41MB Heap size: 3653.24MB +2024-08-07T15:41:39.681745Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:42:16.997982Z | Info | Live bytes: 1290.95MB Heap size: 3653.24MB +2024-08-07T15:42:27.743169Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:42:28.152606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:42:31.042712Z | Info | Cradle path: cardano-api/src/Cardano/Api.hs +2024-08-07T15:42:31.043186Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-07T15:42:31.083497Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:42:32.741854Z | Info | Load cabal cradle using single file +2024-08-07T15:42:33.358435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-07T15:42:34.062158Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT311363-195 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-07T15:42:38.681794Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-4164c91a07d91ad730a4f730787ccd53b9ba7e7b +2024-08-07T15:42:38.682009Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-gen-4164c91a07d91ad730a4f730787ccd53b9ba7e7b +2024-08-07T15:42:38.682115Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-4164c91a07d91ad730a4f730787ccd53b9ba7e7b +2024-08-07T15:42:38.688502Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.1.0.0-inplace + , cardano-api-9.1.0.0-inplace-gen + , cardano-api-9.1.0.0-inplace-internal ] +2024-08-07T15:42:45.932113Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-08-07T15:43:17.028389Z | Info | Live bytes: 1703.16MB Heap size: 4493.15MB +2024-08-07T15:44:17.089063Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:45:17.149561Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:46:17.162570Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:47:17.223145Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:48:17.257502Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:49:17.318149Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:50:17.378523Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:51:17.438752Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:52:17.475780Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:53:17.486283Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:54:17.546998Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:55:17.607624Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:56:17.668335Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:57:17.729159Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:58:17.789903Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T15:59:17.850669Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:00:17.911452Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:01:17.955733Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:02:17.987721Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:03:18.048390Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:04:18.109091Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:05:18.123677Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:06:18.179741Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:07:18.203741Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:08:18.264392Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:09:18.315705Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:10:18.376366Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:11:18.403786Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:12:18.464463Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:13:18.525117Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:14:18.585741Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:15:18.646407Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:16:18.707028Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:17:18.728825Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:18:18.755670Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:19:18.783994Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:20:18.819730Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:21:18.880371Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:22:18.892473Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:23:18.910521Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:24:18.947670Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:25:18.970111Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:26:18.979660Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:27:19.040169Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:28:19.100609Z | Info | Live bytes: 1707.16MB Heap size: 4493.15MB +2024-08-07T16:29:01.865384Z | Info | LSP: received shutdown +2024-08-07T16:29:01.870277Z | Error | Got EOF +2024-08-08 13:59:48.6400000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-08 13:59:48.6420000 [client] INFO Finding haskell-language-server +2024-08-08 13:59:48.6430000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:48.6430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:48.6480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-08 13:59:49.1180000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:49.1180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:49.1240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-08 13:59:49.2500000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:49.2510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:49.2570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-08 13:59:49.3640000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:49.3650000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:49.3720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-08 13:59:49.4820000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:49.4820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:49.4870000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-08 13:59:49.5050000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:49.5050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:49.5100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-08 13:59:49.5270000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:49.5280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:49.5330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-08 13:59:49.5520000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-08 13:59:49.6740000 [client] INFO Checking for ghcup installation +2024-08-08 13:59:49.6740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 13:59:49.6790000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-08 13:59:49.8060000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-08 13:59:49.8060000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-08 14:00:02.0010000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-08-08 14:00:02.3040000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-08 14:00:02.3040000 [client] INFO Checking for ghcup installation +2024-08-08 14:00:02.3050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 14:00:02.3140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-08 14:00:02.4010000 [client] INFO Checking for ghcup installation +2024-08-08 14:00:02.4010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 14:00:02.4070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-08 14:00:02.4240000 [client] INFO Checking for ghcup installation +2024-08-08 14:00:02.4240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 14:00:02.4280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-08 14:00:02.4420000 [client] INFO Checking for ghcup installation +2024-08-08 14:00:02.4430000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 14:00:02.4460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-08-08 14:00:02.4610000 [client] INFO Checking for ghcup installation +2024-08-08 14:00:02.4610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-08 14:00:02.4690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-08-08 14:00:02.5750000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-08 14:00:02.5760000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-08 14:00:02.5760000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-08 14:00:02.5760000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-08 14:00:02.5760000 [client] INFO server environment variables: +2024-08-08 14:00:02.5760000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-08 14:00:02.5760000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-08 14:00:02.5760000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-08 14:00:02.5770000 [client] INFO Starting language server +2024-08-08T14:00:12.789990Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-08-08T14:00:12.791692Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-08T14:00:12.791845Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-08T14:00:12.795530Z | Info | Logging heap statistics every 60.00s +2024-08-08T14:00:12.802324Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-08T14:00:12.802695Z | Info | Starting server +2024-08-08T14:00:12.816066Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-08T14:00:12.926534Z | Info | Started LSP server in 0.12s +2024-08-08T14:00:14.262385Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-08-08T14:00:14.262940Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-08T14:00:14.838773Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:00:15.859878Z | Info | Load cabal cradle using single file +2024-08-08T14:00:16.839583Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT45214-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-08T14:00:19.106764Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:00:27.845955Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:00:39.309303Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-3eb22827ab0a27544f6d79a7b80afd417e6fbbbb +2024-08-08T14:00:39.314194Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.1.0.0-inplace-internal] +2024-08-08T14:00:45.604712Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:01:12.815582Z | Info | Live bytes: 713.14MB Heap size: 2192.57MB +2024-08-08T14:02:12.843256Z | Info | Live bytes: 713.14MB Heap size: 2192.57MB +2024-08-08T14:03:09.696870Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:03:12.198158Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:03:12.844475Z | Info | Live bytes: 729.17MB Heap size: 2192.57MB +2024-08-08T14:03:22.583081Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:03:33.961730Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:04:12.868444Z | Info | Live bytes: 872.73MB Heap size: 2192.57MB +2024-08-08T14:05:12.929894Z | Info | Live bytes: 872.73MB Heap size: 2192.57MB +2024-08-08T14:06:12.954950Z | Info | Live bytes: 872.73MB Heap size: 2192.57MB +2024-08-08T14:07:13.015721Z | Info | Live bytes: 872.73MB Heap size: 2192.57MB +2024-08-08T14:08:13.077012Z | Info | Live bytes: 872.73MB Heap size: 2192.57MB +2024-08-08T14:09:13.138028Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:10:13.198812Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:11:13.259862Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:12:13.321458Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:13:13.382434Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:14:13.443480Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:15:13.504651Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:16:13.523359Z | Info | Live bytes: 886.65MB Heap size: 2192.57MB +2024-08-08T14:16:29.518930Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:16:31.475105Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-08T14:16:35.228074Z | Info | LSP: received shutdown +2024-08-08T14:16:35.230029Z | Info | Reactor thread stopped +2024-08-08T14:16:35.230390Z | Error | Got EOF +2024-08-12 13:24:09.7310000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-12 13:24:09.7330000 [client] INFO Finding haskell-language-server +2024-08-12 13:24:09.7340000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:09.7340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:09.7410000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-12 13:24:10.6740000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:10.6740000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:10.6810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-12 13:24:10.8070000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:10.8080000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:10.8120000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-12 13:24:10.9270000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:10.9270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:10.9340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-12 13:24:11.0360000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:11.0360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:11.0390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-12 13:24:11.0530000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:11.0530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:11.0580000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-12 13:24:11.0710000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:11.0710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:11.0760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-12 13:24:11.0960000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-12 13:24:11.2320000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:11.2320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:11.2390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-12 13:24:11.3950000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-12 13:24:11.3950000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-12 13:24:24.4940000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-08-12 13:24:24.9070000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-12 13:24:24.9070000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:24.9070000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:24.9140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-12 13:24:25.0090000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:25.0090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:25.0140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-12 13:24:25.0320000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:25.0320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:25.0370000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-12 13:24:25.0510000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:25.0510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:25.0560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-08-12 13:24:25.0720000 [client] INFO Checking for ghcup installation +2024-08-12 13:24:25.0720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-12 13:24:25.0770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-08-12 13:24:25.1920000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-12 13:24:25.1930000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-12 13:24:25.1930000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-12 13:24:25.1930000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-12 13:24:25.1930000 [client] INFO server environment variables: +2024-08-12 13:24:25.1930000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-12 13:24:25.1930000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-12 13:24:25.1930000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-12 13:24:25.1940000 [client] INFO Starting language server +2024-08-12T13:24:36.300352Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-08-12T13:24:36.301903Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-12T13:24:36.302111Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-12T13:24:36.304628Z | Info | Logging heap statistics every 60.00s +2024-08-12T13:24:36.311789Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-12T13:24:36.312480Z | Info | Starting server +2024-08-12T13:24:36.326722Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-12T13:24:36.380169Z | Info | Started LSP server in 0.07s +2024-08-12T13:24:37.808619Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Script.hs +2024-08-12T13:24:37.809831Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-12T13:24:38.213735Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-12T13:24:39.391256Z | Info | Load cabal cradle using single file +2024-08-12T13:24:40.458699Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT42818-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-12T13:24:41.474202Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-12T13:24:50.486104Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.1.0.0-inplace-internal-3eb22827ab0a27544f6d79a7b80afd417e6fbbbb +2024-08-12T13:24:50.492361Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.1.0.0-inplace-internal] +2024-08-12T13:24:52.090769Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Script.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-08-12T13:25:36.316465Z | Info | Live bytes: 627.04MB Heap size: 1784.68MB +2024-08-12T13:25:39.529728Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-12T13:26:36.370247Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:27:36.430140Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:28:36.438316Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:29:36.498522Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:30:36.558153Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:31:36.584419Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:32:36.644213Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:33:36.704158Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:34:36.764179Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:35:36.824222Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:36:36.865827Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:37:36.895858Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:38:36.908156Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:39:36.969208Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:40:37.000494Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:41:37.039855Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:42:37.046497Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:43:37.107637Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:44:37.110442Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:45:37.169907Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:46:37.174546Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:47:37.230843Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:48:37.291674Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:49:37.326359Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:50:37.371362Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:51:37.406183Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:52:37.434409Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:53:37.495208Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:54:37.555998Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:55:37.566413Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:56:37.627256Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:57:37.648680Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:58:37.709656Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T13:59:37.718407Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:00:37.746292Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:01:37.807124Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:02:37.867757Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:03:37.928308Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:04:37.988165Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:05:38.048262Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:06:38.078003Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:07:38.134387Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:08:38.141620Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:09:38.149282Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:10:38.209929Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:11:38.230273Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:12:38.291163Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:13:38.294658Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:14:38.355942Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:15:38.416807Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:16:38.430484Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:17:38.486349Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:18:38.535122Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:19:38.577922Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:20:38.638577Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:21:38.698209Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:22:38.758936Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:23:38.816341Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:24:38.877327Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:25:38.896769Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:26:38.957275Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:27:38.970818Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:28:39.031159Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:29:39.056385Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:30:39.070807Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:31:39.131137Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:32:39.183074Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:33:39.243715Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:34:39.304312Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:35:39.365101Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:36:39.401120Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:37:39.462079Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:38:39.509771Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:39:39.550531Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:40:39.611838Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:41:39.673149Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:42:39.734949Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:43:39.796375Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:44:39.857386Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:45:39.918753Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:46:39.970356Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:47:39.971744Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:48:40.032461Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:49:40.093233Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:50:40.153269Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:51:40.214058Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:52:40.274682Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:53:40.335220Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:54:40.395761Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:55:40.438211Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:56:40.498696Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:57:40.559488Z | Info | Live bytes: 644.36MB Heap size: 1809.84MB +2024-08-12T14:57:55.901664Z | Info | LSP: received shutdown +2024-08-12T14:57:55.903444Z | Info | Reactor thread stopped +2024-08-12T14:57:55.905700Z | Error | Got EOF +2024-08-13 14:16:35.9430000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-13 14:16:35.9450000 [client] INFO Finding haskell-language-server +2024-08-13 14:16:35.9460000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:35.9460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:35.9550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-13 14:16:36.4720000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:36.4720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:36.4770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-13 14:16:36.5840000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:36.5840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:36.5890000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-13 14:16:36.6950000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:36.6950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:36.7000000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-13 14:16:36.8000000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:36.8010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:36.8040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-13 14:16:36.8180000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:36.8180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:36.8230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-13 14:16:36.8620000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:36.8620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:36.8680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-13 14:16:36.8870000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-13 14:16:36.9940000 [client] INFO Checking for ghcup installation +2024-08-13 14:16:36.9940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:16:37.0000000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-13 14:16:37.0940000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-13 14:16:37.0950000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-13 14:17:04.0920000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-13 14:17:04.3870000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-13 14:17:04.3870000 [client] INFO Checking for ghcup installation +2024-08-13 14:17:04.3870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:17:04.3910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-13 14:17:04.4770000 [client] INFO Checking for ghcup installation +2024-08-13 14:17:04.4770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:17:04.4830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-13 14:17:04.4990000 [client] INFO Checking for ghcup installation +2024-08-13 14:17:04.4990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:17:04.5040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-13 14:17:04.5180000 [client] INFO Checking for ghcup installation +2024-08-13 14:17:04.5180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:17:04.5220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-13 14:17:04.5360000 [client] INFO Checking for ghcup installation +2024-08-13 14:17:04.5360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-13 14:17:04.5400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-13 14:17:04.6440000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-13 14:17:04.6440000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-13 14:17:04.6440000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-13 14:17:04.6440000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-13 14:17:04.6450000 [client] INFO server environment variables: +2024-08-13 14:17:04.6450000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-13 14:17:04.6450000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-13 14:17:04.6450000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-13 14:17:04.6470000 [client] INFO Starting language server +2024-08-13T14:17:15.380385Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-13T14:17:15.382015Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-13T14:17:15.382353Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-13T14:17:15.384978Z | Info | Logging heap statistics every 60.00s +2024-08-13T14:17:15.391755Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-13T14:17:15.392218Z | Info | Starting server +2024-08-13T14:17:15.406300Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-13T14:17:15.499712Z | Info | Started LSP server in 0.11s +2024-08-13T14:17:16.736077Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Eon/ShelleyBasedEra.hs +2024-08-13T14:17:16.737201Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-13T14:17:17.158038Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-13T14:17:18.166625Z | Info | LSP: received shutdown +2024-08-13T14:17:18.171498Z | Error | Got EOF +2024-08-14 20:19:28.3990000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-14 20:19:28.4000000 [client] INFO Finding haskell-language-server +2024-08-14 20:19:28.4010000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:28.4010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:28.4070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-14 20:19:28.5560000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:28.5560000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:28.5600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-14 20:19:28.7520000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:28.7530000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:28.7570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-14 20:19:28.9370000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:28.9370000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:28.9430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-14 20:19:29.0540000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:29.0540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:29.0610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-14 20:19:29.0810000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:29.0810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:29.0870000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-14 20:19:29.1030000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:29.1030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:29.1090000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-14 20:19:29.1290000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-14 20:19:29.1630000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:29.1630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:29.1680000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-14 20:19:29.2830000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-14 20:19:29.2840000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-14 20:19:44.1120000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-14 20:19:44.2680000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-14 20:19:44.2680000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:44.2680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:44.2730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-14 20:19:44.3680000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:44.3680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:44.3730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-14 20:19:44.3900000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:44.3900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:44.3950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-14 20:19:44.4090000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:44.4090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:44.4140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-14 20:19:44.4290000 [client] INFO Checking for ghcup installation +2024-08-14 20:19:44.4290000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 20:19:44.4340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-14 20:19:44.5600000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-14 20:19:44.5610000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-14 20:19:44.5610000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-14 20:19:44.5610000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-14 20:19:44.5610000 [client] INFO server environment variables: +2024-08-14 20:19:44.5610000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-14 20:19:44.5610000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-14 20:19:44.5610000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-14 20:19:44.5630000 [client] INFO Starting language server +2024-08-14T20:20:18.101228Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-14T20:20:18.102880Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-14T20:20:18.103048Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-14T20:20:18.105236Z | Info | Logging heap statistics every 60.00s +2024-08-14T20:20:18.112637Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-14T20:20:18.112996Z | Info | Starting server +2024-08-14T20:20:18.126491Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-14T20:20:18.155318Z | Info | Started LSP server in 0.04s +2024-08-14T20:20:19.337818Z | Info | LSP: received shutdown +2024-08-14T20:20:19.338399Z | Info | Reactor thread stopped +2024-08-14T20:20:19.344447Z | Error | Got EOF +2024-08-14 21:23:32.8520000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-14 21:23:32.8530000 [client] INFO Finding haskell-language-server +2024-08-14 21:23:32.8540000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:32.8540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:32.8610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-14 21:23:33.1720000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:33.1720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:33.1780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-14 21:23:33.2930000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:33.2930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:33.2980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-14 21:23:33.4280000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:33.4280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:33.4330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-14 21:23:33.5630000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:33.5630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:33.5670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-14 21:23:33.5800000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:33.5810000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:33.5850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-14 21:23:33.5990000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:33.5990000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:33.6030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-14 21:23:33.6200000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-14 21:23:33.7340000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:33.7340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:33.7390000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-14 21:23:33.8640000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-14 21:23:33.8640000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-14 21:23:41.6780000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-14 21:23:41.6870000 [client] INFO Reading cached release data at /home/jordan/.config/Code/User/globalStorage/haskell.haskell/ghcupReleases.cache.json +2024-08-14 21:23:41.6890000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-14 21:23:41.6900000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:41.6900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:41.6950000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-14 21:23:41.7890000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:41.7890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:41.7940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-14 21:23:41.8090000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:41.8090000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:41.8130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-14 21:23:41.8260000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:41.8260000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:41.8310000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-14 21:23:41.8440000 [client] INFO Checking for ghcup installation +2024-08-14 21:23:41.8440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-14 21:23:41.8480000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-14 21:23:41.9510000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-14 21:23:41.9520000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-14 21:23:41.9520000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-14 21:23:41.9520000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-14 21:23:41.9520000 [client] INFO server environment variables: +2024-08-14 21:23:41.9520000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-14 21:23:41.9520000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-14 21:23:41.9520000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-14 21:23:41.9530000 [client] INFO Starting language server +2024-08-14T21:23:51.666230Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-14T21:23:51.667791Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-14T21:23:51.667958Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-14T21:23:51.670724Z | Info | Logging heap statistics every 60.00s +2024-08-14T21:23:51.677669Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-14T21:23:51.678027Z | Info | Starting server +2024-08-14T21:23:51.692116Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-14T21:23:51.719648Z | Info | Started LSP server in 0.04s +2024-08-14T21:23:52.847676Z | Info | LSP: received shutdown +2024-08-14T21:23:52.848789Z | Info | Reactor thread stopped +2024-08-14T21:23:52.859225Z | Warning | LSP: received message during shutdown: "initialized" +2024-08-14T21:23:52.859884Z | Warning | LSP: received message during shutdown: "workspace/didChangeConfiguration" +2024-08-14T21:23:52.860783Z | Warning | LSP: received message during shutdown: "textDocument/didOpen" +2024-08-14T21:23:52.862485Z | Error | Got EOF +2024-08-15 14:22:29.7830000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-15 14:22:29.7840000 [client] INFO Finding haskell-language-server +2024-08-15 14:22:29.7850000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:29.7860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:29.7920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-15 14:22:30.3600000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:30.3600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:30.3650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-15 14:22:30.5200000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:30.5200000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:30.5260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-15 14:22:30.6510000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:30.6510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:30.6570000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-15 14:22:30.7780000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:30.7780000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:30.7820000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-15 14:22:30.7980000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:30.7980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:30.8030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-15 14:22:30.8170000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:30.8170000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:30.8220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-15 14:22:30.8400000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-15 14:22:30.9580000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:30.9580000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:30.9620000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-15 14:22:31.0760000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-15 14:22:31.0760000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-15 14:22:38.8420000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-15 14:22:39.3630000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-15 14:22:39.3630000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:39.3630000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:39.3670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-15 14:22:39.4300000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:39.4300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:39.4340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-15 14:22:39.4480000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:39.4480000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:39.4510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-15 14:22:39.4640000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:39.4640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:39.4670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-15 14:22:39.4800000 [client] INFO Checking for ghcup installation +2024-08-15 14:22:39.4800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 14:22:39.4830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-15 14:22:39.5670000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-15 14:22:39.5680000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-15 14:22:39.5680000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-15 14:22:39.5680000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-15 14:22:39.5680000 [client] INFO server environment variables: +2024-08-15 14:22:39.5680000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-15 14:22:39.5680000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-15 14:22:39.5680000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-15 14:22:39.5690000 [client] INFO Starting language server +2024-08-15T14:22:48.784454Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-15T14:22:48.786133Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-15T14:22:48.786377Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-15T14:22:48.788623Z | Info | Logging heap statistics every 60.00s +2024-08-15T14:22:48.795000Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-15T14:22:48.795358Z | Info | Starting server +2024-08-15T14:22:48.809056Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-15T14:22:48.836599Z | Info | Started LSP server in 0.04s +2024-08-15T14:22:49.943632Z | Info | Cradle path: cardano-api/internal/Cardano/Api/IPC.hs +2024-08-15T14:22:49.944533Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-15T14:22:50.436099Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-15T14:22:51.212047Z | Info | Load cabal cradle using single file +2024-08-15T14:22:52.051086Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT4911-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-15T14:23:48.847854Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-15T14:24:48.907710Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-15T14:25:16.170915Z | Info | LSP: received shutdown +2024-08-15T14:25:16.184289Z | Info | Reactor thread stopped +2024-08-15T14:25:16.200129Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T14:25:16.200750Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T14:25:16.200914Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T14:25:16.201062Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T14:25:16.207864Z | Error | Got EOF +2024-08-15 19:41:45.8690000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-15 19:41:45.8700000 [client] INFO Finding haskell-language-server +2024-08-15 19:41:45.8720000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:45.8720000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:45.8780000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-15 19:41:46.2680000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:46.2680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:46.2730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-15 19:41:46.5270000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:46.5270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:46.5330000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-15 19:41:46.7680000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:46.7680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:46.7730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-15 19:41:46.9620000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:46.9620000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:46.9660000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-15 19:41:46.9790000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:46.9790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:46.9830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-15 19:41:46.9960000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:46.9960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:47.0010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-15 19:41:47.0200000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-15 19:41:47.1190000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:47.1190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:47.1230000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-15 19:41:47.3680000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-15 19:41:47.3690000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-15 19:41:55.1370000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-15 19:41:55.1480000 [client] INFO Reading cached release data at /home/jordan/.config/Code/User/globalStorage/haskell.haskell/ghcupReleases.cache.json +2024-08-15 19:41:55.1500000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-15 19:41:55.1500000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:55.1500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:55.1550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-15 19:41:55.2390000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:55.2390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:55.2430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-15 19:41:55.2570000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:55.2570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:55.2600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-15 19:41:55.2730000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:55.2730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:55.2760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-15 19:41:55.2890000 [client] INFO Checking for ghcup installation +2024-08-15 19:41:55.2890000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 19:41:55.2930000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-15 19:41:55.3860000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-15 19:41:55.3860000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-15 19:41:55.3860000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-15 19:41:55.3860000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-15 19:41:55.3870000 [client] INFO server environment variables: +2024-08-15 19:41:55.3870000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-15 19:41:55.3870000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-15 19:41:55.3870000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-15 19:41:55.3880000 [client] INFO Starting language server +2024-08-15T19:42:05.082981Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-15T19:42:05.084805Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-15T19:42:05.084973Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-15T19:42:05.087498Z | Info | Logging heap statistics every 60.00s +2024-08-15T19:42:05.094763Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-15T19:42:05.095246Z | Info | Starting server +2024-08-15T19:42:05.108274Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-15T19:42:05.136977Z | Info | Started LSP server in 0.04s +2024-08-15T19:42:06.241253Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query.hs +2024-08-15T19:42:06.242101Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-15T19:42:06.786921Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-15T19:42:07.536604Z | Info | Load cabal cradle using single file +2024-08-15T19:42:08.375816Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT4087-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-15T19:43:05.142756Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-15T19:44:05.146070Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-15T19:44:10.237460Z | Info | LSP: received shutdown +2024-08-15T19:44:10.240502Z | Info | Reactor thread stopped +2024-08-15T19:44:10.241095Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T19:44:10.241442Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T19:44:10.241686Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T19:44:10.244132Z | Error | Got EOF +2024-08-15 22:11:27.4130000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-15 22:11:27.4150000 [client] INFO Finding haskell-language-server +2024-08-15 22:11:27.4160000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:27.4160000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:27.4220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-15 22:11:27.9500000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:27.9500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:27.9550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-15 22:11:28.1030000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:28.1030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:28.1070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-15 22:11:28.2120000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:28.2120000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:28.2160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-15 22:11:28.3140000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:28.3140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:28.3180000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-15 22:11:28.3310000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:28.3310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:28.3340000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-15 22:11:28.3470000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:28.3470000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:28.3500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-15 22:11:28.3660000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-15 22:11:28.4700000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:28.4700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:28.4740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-15 22:11:28.5980000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-15 22:11:28.5980000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-15 22:11:36.6840000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-15 22:11:37.0690000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-15 22:11:37.0690000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:37.0690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:37.0720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-15 22:11:37.1460000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:37.1460000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:37.1500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-15 22:11:37.1640000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:37.1640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:37.1670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-15 22:11:37.1800000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:37.1800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:37.1830000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-15 22:11:37.1960000 [client] INFO Checking for ghcup installation +2024-08-15 22:11:37.1960000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-15 22:11:37.1990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-15 22:11:37.2930000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-15 22:11:37.2940000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-15 22:11:37.2940000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-15 22:11:37.2940000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-15 22:11:37.2940000 [client] INFO server environment variables: +2024-08-15 22:11:37.2940000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-15 22:11:37.2940000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-15 22:11:37.2940000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-15 22:11:37.2970000 [client] INFO Starting language server +2024-08-15T22:11:46.722503Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-15T22:11:46.724137Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-15T22:11:46.724451Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-15T22:11:46.726677Z | Info | Logging heap statistics every 60.00s +2024-08-15T22:11:46.733225Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-15T22:11:46.733494Z | Info | Starting server +2024-08-15T22:11:46.746009Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-15T22:11:46.774526Z | Info | Started LSP server in 0.04s +2024-08-15T22:11:47.912104Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query.hs +2024-08-15T22:11:47.912965Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-15T22:11:48.458085Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-15T22:11:49.290428Z | Info | Load cabal cradle using single file +2024-08-15T22:11:50.172817Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT10081-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-15T22:12:17.390361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-15T22:12:46.735113Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-15T22:13:46.795382Z | Info | Live bytes: 44.28MB Heap size: 1167.07MB +2024-08-15T22:14:26.149319Z | Info | LSP: received shutdown +2024-08-15T22:14:26.151347Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T22:14:26.151633Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T22:14:26.151875Z | Info | Reactor thread stopped +2024-08-15T22:14:26.152577Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T22:14:26.152750Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T22:14:26.153523Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-15T22:14:26.159617Z | Error | Got EOF +2024-08-16 17:13:20.8330000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-16 17:13:20.8330000 [client] INFO Finding haskell-language-server +2024-08-16 17:13:20.8340000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:20.8340000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:20.8400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-16 17:13:21.2960000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:21.2970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:21.3010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-16 17:13:21.4980000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:21.4980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:21.5030000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-16 17:13:21.6980000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:21.6980000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:21.7040000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-16 17:13:21.8750000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:21.8760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:21.8800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-16 17:13:21.8970000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:21.8970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:21.9010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-16 17:13:21.9150000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:21.9150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:21.9190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-16 17:13:21.9370000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-16 17:13:22.0050000 [client] INFO Checking for ghcup installation +2024-08-16 17:13:22.0050000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 17:13:22.0100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-16 17:13:22.2160000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-16 17:13:22.2160000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-16 18:05:42.6120000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-16 18:05:42.6130000 [client] INFO Finding haskell-language-server +2024-08-16 18:05:42.6140000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:42.6140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:42.6200000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-16 18:05:43.5170000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:43.5170000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:43.5240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-16 18:05:43.6210000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:43.6210000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:43.6270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-16 18:05:43.7230000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:43.7230000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:43.7270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-16 18:05:43.8150000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:43.8150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:43.8190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-16 18:05:43.8320000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:43.8320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:43.8350000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-16 18:05:43.8490000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:43.8490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:43.8520000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-16 18:05:43.8680000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-16 18:05:43.8920000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:43.8920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:43.8960000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-16 18:05:44.0010000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-16 18:05:44.0010000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-16 18:05:46.1700000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-16 18:05:46.3800000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-16 18:05:46.3800000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:46.3800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:46.3840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-16 18:05:46.4570000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:46.4570000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:46.4610000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-16 18:05:46.4760000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:46.4760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:46.4800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-16 18:05:46.4930000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:46.4930000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:46.4970000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-16 18:05:46.5100000 [client] INFO Checking for ghcup installation +2024-08-16 18:05:46.5100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 18:05:46.5130000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-16 18:05:46.5970000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-16 18:05:46.5980000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-16 18:05:46.5980000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-16 18:05:46.5980000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-16 18:05:46.5980000 [client] INFO server environment variables: +2024-08-16 18:05:46.5980000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-16 18:05:46.5980000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-16 18:05:46.5980000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-16 18:05:46.5990000 [client] INFO Starting language server +2024-08-16T18:05:56.431792Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-16T18:05:56.432923Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-16T18:05:56.433398Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-16T18:05:56.436836Z | Info | Logging heap statistics every 60.00s +2024-08-16T18:05:56.444488Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-16T18:05:56.444871Z | Info | Starting server +2024-08-16T18:05:56.446496Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-16T18:05:56.470883Z | Info | Started LSP server in 0.03s +2024-08-16T18:05:57.615264Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query.hs +2024-08-16T18:05:57.615862Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-16T18:05:58.160304Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T18:05:58.924142Z | Info | Load cabal cradle using single file +2024-08-16T18:05:59.786497Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT95934-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-16T18:06:56.495428Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:07:56.548464Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:08:56.608492Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:09:56.669142Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:10:56.716582Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:11:56.759324Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:12:56.760973Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:13:56.821712Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:14:56.829624Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-16T18:15:24.329152Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-4038d54d7016811a700b4ec46bf347dd42faf01c +2024-08-16T18:15:24.333572Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-16T18:15:56.854146Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:16:56.914906Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:17:56.975605Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:18:57.036275Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:19:57.096975Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:20:57.138461Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:21:57.199186Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:22:57.259891Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:23:57.273486Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:24:57.275890Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:25:57.334475Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:26:57.394411Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:27:57.455141Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:28:57.472190Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:29:57.506859Z | Info | Live bytes: 682.32MB Heap size: 1884.29MB +2024-08-16T18:30:01.126343Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T18:30:21.917269Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T18:30:33.392159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T18:30:53.597537Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T18:30:57.510190Z | Info | Live bytes: 547.85MB Heap size: 2334.13MB +2024-08-16T18:31:57.512409Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:32:57.524587Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:33:57.585251Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:34:57.586433Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:35:57.646976Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:36:57.707559Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:37:57.768106Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:38:57.828599Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:39:57.889039Z | Info | Live bytes: 549.98MB Heap size: 2334.13MB +2024-08-16T18:40:57.939988Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:41:57.948777Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:42:58.009321Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:43:58.036355Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:44:58.097083Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:45:58.130462Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:46:58.162389Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:47:58.222968Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:48:58.283710Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:49:58.344360Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:50:58.405138Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:51:58.450538Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:52:58.482484Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:53:58.514485Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:54:58.560675Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:55:58.577178Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:56:58.637532Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:57:58.698075Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:58:58.758696Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T18:59:58.819206Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T19:00:58.879717Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T19:01:58.887160Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T19:02:58.947681Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T19:03:58.949691Z | Info | Live bytes: 559.97MB Heap size: 2334.13MB +2024-08-16T19:04:41.598042Z | Error | Got EOF +2024-08-16 21:37:43.8290000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-16 21:37:43.8310000 [client] INFO Finding haskell-language-server +2024-08-16 21:37:43.8320000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:43.8320000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:43.8380000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-16 21:37:44.3180000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:44.3190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:44.3240000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-16 21:37:44.7300000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:44.7300000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:44.7350000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-16 21:37:44.9500000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:44.9500000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:44.9550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-16 21:37:45.2790000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:45.2790000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:45.2850000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-16 21:37:45.3010000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:45.3010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:45.3070000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-16 21:37:45.3240000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:45.3240000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:45.3320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-16 21:37:45.3520000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-16 21:37:45.5680000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:45.5680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:45.5750000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-16 21:37:45.9820000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-16 21:37:45.9830000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-16 21:37:54.4490000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-16 21:37:54.4700000 [client] INFO Reading cached release data at /home/jordan/.config/Code/User/globalStorage/haskell.haskell/ghcupReleases.cache.json +2024-08-16 21:37:54.4710000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-16 21:37:54.4710000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:54.4710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:54.4760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-16 21:37:54.6310000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:54.6310000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:54.6350000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-16 21:37:54.6510000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:54.6510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:54.6550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-16 21:37:54.6690000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:54.6690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:54.6730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-16 21:37:54.6870000 [client] INFO Checking for ghcup installation +2024-08-16 21:37:54.6870000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-16 21:37:54.6910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-16 21:37:54.8360000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-16 21:37:54.8360000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-16 21:37:54.8360000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-16 21:37:54.8360000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-16 21:37:54.8360000 [client] INFO server environment variables: +2024-08-16 21:37:54.8360000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-16 21:37:54.8360000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-16 21:37:54.8360000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-16 21:37:54.8370000 [client] INFO Starting language server +2024-08-16T21:38:04.610718Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-16T21:38:04.612407Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-16T21:38:04.612567Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-16T21:38:04.614941Z | Info | Logging heap statistics every 60.00s +2024-08-16T21:38:04.621617Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-16T21:38:04.622037Z | Info | Starting server +2024-08-16T21:38:04.636445Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-16T21:38:04.735181Z | Info | Started LSP server in 0.11s +2024-08-16T21:38:05.960684Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query.hs +2024-08-16T21:38:05.961273Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-16T21:38:06.456049Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T21:38:06.456144Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T21:38:07.488050Z | Info | Load cabal cradle using single file +2024-08-16T21:38:08.351332Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT4973-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-16T21:38:11.350899Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-4038d54d7016811a700b4ec46bf347dd42faf01c +2024-08-16T21:38:11.354975Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-16T21:39:04.616826Z | Info | Live bytes: 557.47MB Heap size: 1768.95MB +2024-08-16T21:40:04.651373Z | Info | Live bytes: 557.47MB Heap size: 1768.95MB +2024-08-16T21:41:04.679410Z | Info | Live bytes: 557.47MB Heap size: 1768.95MB +2024-08-16T21:41:28.434159Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T21:42:04.704710Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:43:04.765334Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:44:04.826009Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:45:04.886568Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:46:04.896051Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:47:04.956702Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:48:05.008064Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:49:05.068759Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:50:05.129462Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:51:05.168011Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:52:05.170060Z | Info | Live bytes: 488.90MB Heap size: 2083.52MB +2024-08-16T21:53:04.953681Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T21:53:05.171952Z | Info | Live bytes: 514.30MB Heap size: 2083.52MB +2024-08-16T21:53:07.523510Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T21:53:16.805282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T21:54:05.176232Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T21:55:05.236752Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T21:56:05.297409Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T21:57:05.358010Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T21:58:05.418651Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T21:59:05.479220Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:00:05.539923Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:01:05.600632Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:02:05.661042Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:03:05.680055Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:04:05.740764Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:05:05.760285Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:06:05.818012Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:07:05.855991Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:08:05.863921Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:09:05.866752Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:10:05.871996Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:11:05.932517Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:12:05.942902Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:13:06.000041Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:14:06.059909Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:15:06.120365Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:16:06.168002Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:17:06.192009Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:18:06.239965Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:19:06.277175Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:20:06.337800Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:21:06.384049Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:22:06.389045Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:23:06.449639Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:24:06.510355Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:25:06.571039Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:26:06.626512Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:27:06.670338Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:28:06.730992Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:29:06.791618Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:30:06.846456Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:31:06.906965Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:32:06.967989Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:33:07.028000Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:34:07.087884Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:35:07.148712Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:36:07.209496Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:37:07.219694Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:38:07.247998Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:39:07.280142Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:40:07.315965Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:41:07.377011Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:42:07.437769Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:43:07.453952Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:44:07.492258Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:45:07.552989Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:46:07.590021Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:47:07.650807Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:48:07.695878Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:49:07.728724Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:50:07.764213Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:51:07.824805Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:52:07.849737Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:53:07.883804Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:54:07.944333Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:55:07.984723Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:56:08.045245Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:57:08.105873Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:58:08.127980Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T22:59:08.175981Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:00:08.236647Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:01:08.239966Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:02:08.272034Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:03:08.332690Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:04:08.336033Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:05:08.396705Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:06:08.457562Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:07:08.496021Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:08:08.528048Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:09:08.575781Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:24:20.941392Z | Info | Live bytes: 528.12MB Heap size: 2083.52MB +2024-08-16T23:25:03.635094Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T23:25:09.006572Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T23:25:20.951820Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:26:21.012415Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:27:21.055036Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:28:21.106013Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:29:21.166444Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:30:21.227006Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:31:21.229561Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:32:21.289897Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:33:21.314532Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:34:21.375175Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:35:21.435640Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:36:21.443068Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:37:21.503451Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:38:21.564381Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:39:21.624932Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:40:21.685614Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:41:21.746382Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:42:21.805976Z | Info | Live bytes: 542.45MB Heap size: 2083.52MB +2024-08-16T23:43:21.133352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T23:43:21.807271Z | Info | Live bytes: 599.44MB Heap size: 2083.52MB +2024-08-16T23:44:21.865851Z | Info | Live bytes: 753.21MB Heap size: 2083.52MB +2024-08-16T23:44:51.846770Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T23:45:21.893399Z | Info | Live bytes: 750.93MB Heap size: 2083.52MB +2024-08-16T23:46:21.954004Z | Info | Live bytes: 750.93MB Heap size: 2083.52MB +2024-08-16T23:47:13.412325Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T23:47:21.992552Z | Info | Live bytes: 763.97MB Heap size: 2083.52MB +2024-08-16T23:48:22.029585Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:49:22.090191Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:50:22.150285Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:51:22.210957Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:52:22.271374Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:53:22.331968Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:54:22.333851Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:55:22.393474Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:56:22.454184Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:57:13.968744Z | Info | Cradle path: cardano-api/gen/Test/Gen/Cardano/Api/Typed.hs +2024-08-16T23:57:13.969283Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-16T23:57:13.995622Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-16T23:57:15.531925Z | Info | Load cabal cradle using single file +2024-08-16T23:57:16.504766Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:gen + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT4973-19 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-16T23:57:22.462354Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:58:22.522358Z | Info | Live bytes: 778.14MB Heap size: 2083.52MB +2024-08-16T23:58:25.240278Z | Info | LSP: received shutdown +2024-08-16T23:58:25.242220Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-16T23:58:25.244553Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-16T23:58:25.244926Z | Warning | LSP: received message during shutdown: "$/cancelRequest" +2024-08-16T23:58:25.245377Z | Info | Reactor thread stopped +2024-08-16T23:58:25.248923Z | Error | Got EOF +2024-08-17 17:15:20.8180000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-17 17:15:20.8200000 [client] INFO Finding haskell-language-server +2024-08-17 17:15:20.8210000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:20.8210000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:20.8270000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-17 17:15:21.7110000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:21.7110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:21.7200000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-17 17:15:22.4360000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:22.4360000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:22.4430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-17 17:15:22.6000000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:22.6010000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:22.6060000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-17 17:15:22.7700000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:22.7700000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:22.7760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-17 17:15:22.7920000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:22.7920000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:22.7990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-17 17:15:22.8150000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:22.8150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:22.8190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-17 17:15:22.8390000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-17 17:15:22.9860000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:22.9860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:22.9920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-17 17:15:23.1890000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-17 17:15:23.1900000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-17 17:15:31.8820000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-17 17:15:32.1060000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-17 17:15:32.1060000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:32.1060000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:32.1140000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-17 17:15:32.2100000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:32.2100000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:32.2160000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-17 17:15:32.2340000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:32.2350000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:32.2400000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-17 17:15:32.2540000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:32.2540000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:32.2600000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-17 17:15:32.2760000 [client] INFO Checking for ghcup installation +2024-08-17 17:15:32.2760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-17 17:15:32.2810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-17 17:15:32.3960000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-17 17:15:32.3970000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-17 17:15:32.3970000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-17 17:15:32.3970000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-17 17:15:32.3970000 [client] INFO server environment variables: +2024-08-17 17:15:32.3970000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-17 17:15:32.3970000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-17 17:15:32.3970000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-17 17:15:32.3990000 [client] INFO Starting language server +2024-08-17T17:15:42.782051Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-17T17:15:42.783854Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-17T17:15:42.784017Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-17T17:15:42.786714Z | Info | Logging heap statistics every 60.00s +2024-08-17T17:15:42.793196Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-17T17:15:42.793848Z | Info | Starting server +2024-08-17T17:15:42.807924Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-17T17:15:42.868833Z | Info | Started LSP server in 0.08s +2024-08-17T17:15:44.027351Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Query.hs +2024-08-17T17:15:44.028852Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-17T17:15:44.582262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-17T17:15:44.582262Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-17T17:15:45.366988Z | Info | Load cabal cradle using single file +2024-08-17T17:15:46.237882Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT6622-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-17T17:15:49.774490Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-4038d54d7016811a700b4ec46bf347dd42faf01c +2024-08-17T17:15:49.779765Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-17T17:16:42.815340Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:17:42.833948Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:18:42.894685Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:19:42.899747Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:20:42.914489Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:21:42.970781Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:22:43.031492Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:23:43.054012Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:24:43.097666Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:25:43.129739Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:26:43.190328Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:27:43.250560Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:28:43.310653Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:29:43.371353Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:30:43.431806Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:31:43.492240Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:32:43.548095Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:33:43.577725Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:34:43.581814Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:35:43.641692Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:36:43.702277Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:37:43.762661Z | Info | Live bytes: 404.11MB Heap size: 1649.41MB +2024-08-17T17:38:08.806297Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-17T17:38:09.103651Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Sign.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-08-17T17:38:09.217683Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-17T17:38:09.422723Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Sign.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-08-17T17:38:10.077087Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-17T17:38:10.115940Z | Warning | Typechecked a file which is not currently open in the editor: /home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Tx/Sign.hs +This can indicate a bug which results in excessive memory usage. +This may be a spurious warning if you have recently closed the file. +If you haven't opened this file recently, please file a report on the issue tracker mentioning the HLS version being used, the plugins enabled, and if possible the codebase and file which triggered this warning. +2024-08-17T17:38:43.768811Z | Info | Live bytes: 565.19MB Heap size: 1930.43MB +2024-08-17T17:38:47.699820Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-17T17:39:43.822186Z | Info | Live bytes: 572.76MB Heap size: 1930.43MB +2024-08-17T17:39:48.511323Z | Info | LSP: received shutdown +2024-08-17T17:39:48.518677Z | Error | Got EOF +2024-08-19 17:46:44.2620000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-19 17:46:44.2680000 [client] INFO Finding haskell-language-server +2024-08-19 17:46:44.2690000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.2690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.2740000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-19 17:46:44.4030000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.4030000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.4080000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-19 17:46:44.5510000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.5510000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.5560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-19 17:46:44.6840000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.6840000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.6900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-19 17:46:44.8220000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.8220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.8280000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-19 17:46:44.8480000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.8490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.8560000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-19 17:46:44.8710000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.8710000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.8760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-19 17:46:44.8990000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-19 17:46:44.9380000 [client] INFO Checking for ghcup installation +2024-08-19 17:46:44.9390000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:46:44.9430000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-19 17:46:45.0600000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-19 17:46:45.0610000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-19 17:47:09.2060000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-08-19 17:47:09.3820000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-19 17:47:09.3820000 [client] INFO Checking for ghcup installation +2024-08-19 17:47:09.3820000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:47:09.3860000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-19 17:47:09.4590000 [client] INFO Checking for ghcup installation +2024-08-19 17:47:09.4600000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:47:09.4640000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-19 17:47:09.4800000 [client] INFO Checking for ghcup installation +2024-08-19 17:47:09.4800000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:47:09.4840000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-19 17:47:09.4970000 [client] INFO Checking for ghcup installation +2024-08-19 17:47:09.4970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:47:09.5010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-08-19 17:47:09.5150000 [client] INFO Checking for ghcup installation +2024-08-19 17:47:09.5150000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-19 17:47:09.5190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-08-19 17:47:09.6330000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-19 17:47:09.6340000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-19 17:47:09.6340000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-19 17:47:09.6340000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-19 17:47:09.6340000 [client] INFO server environment variables: +2024-08-19 17:47:09.6340000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-19 17:47:09.6340000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-19 17:47:09.6340000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-19 17:47:09.6350000 [client] INFO Starting language server +2024-08-19T17:47:18.732620Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-08-19T17:47:18.742982Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-19T17:47:18.743238Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-19T17:47:18.745759Z | Info | Logging heap statistics every 60.00s +2024-08-19T17:47:18.752361Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-19T17:47:18.752971Z | Info | Starting server +2024-08-19T17:47:18.754288Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-19T17:47:18.799515Z | Info | Started LSP server in 0.05s +2024-08-19T17:47:19.959295Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-08-19T17:47:19.960478Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-19T17:47:20.482296Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-19T17:47:21.359365Z | Info | Load cabal cradle using single file +2024-08-19T17:47:22.246368Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT10684-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-19T17:47:30.858894Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-cc3e0d6750e2c384d753830f3552dc9ecad6ee90 +2024-08-19T17:47:30.863504Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-19T17:48:18.781868Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:49:18.839175Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:50:18.857377Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:51:18.918013Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:52:18.922951Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:53:18.954925Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:54:19.015675Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:55:19.018862Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:56:19.064982Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:57:19.081113Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:58:19.140862Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T17:59:19.195865Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T18:00:19.256529Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T18:01:19.309855Z | Info | Live bytes: 679.80MB Heap size: 2365.59MB +2024-08-19T18:01:21.242295Z | Error | Got EOF +2024-08-20 12:39:01.8700000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-20 12:39:01.8710000 [client] INFO Finding haskell-language-server +2024-08-20 12:39:01.8730000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:01.8730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:01.8810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-20 12:39:02.5550000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:02.5550000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:02.5650000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-20 12:39:02.8010000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:02.8020000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:02.8100000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-20 12:39:02.9660000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:02.9660000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:02.9720000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-20 12:39:03.1680000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:03.1680000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:03.1760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-20 12:39:03.1910000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:03.1910000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:03.1990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-20 12:39:03.2140000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:03.2140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:03.2220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-20 12:39:03.2460000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-20 12:39:03.3940000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:03.3940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:03.3990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-20 12:39:03.6260000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-20 12:39:03.6270000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-20 12:39:17.7350000 [client] INFO The GHC version for the project or file: 9.6.5 +2024-08-20 12:39:17.9940000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-20 12:39:17.9940000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:17.9950000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:17.9990000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-20 12:39:18.0730000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:18.0730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:18.0770000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-20 12:39:18.0940000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:18.0940000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:18.0980000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-20 12:39:18.1110000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:18.1110000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:18.1150000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.6.5' in cwd '/home/jordan' +2024-08-20 12:39:18.1280000 [client] INFO Checking for ghcup installation +2024-08-20 12:39:18.1280000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-20 12:39:18.1320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.6.5 --install' in cwd '/home/jordan' +2024-08-20 12:39:18.2160000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-20 12:39:18.2170000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-20 12:39:18.2170000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-20 12:39:18.2170000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-20 12:39:18.2170000 [client] INFO server environment variables: +2024-08-20 12:39:18.2170000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-20 12:39:18.2170000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-20 12:39:18.2170000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.6.5_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-20 12:39:18.2190000 [client] INFO Starting language server +2024-08-20T12:39:27.984654Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.6.5) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.6.5) +2024-08-20T12:39:27.985704Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-20T12:39:27.985884Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-20T12:39:27.988076Z | Info | Logging heap statistics every 60.00s +2024-08-20T12:39:27.994898Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-20T12:39:27.995283Z | Info | Starting server +2024-08-20T12:39:27.996800Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-20T12:39:28.075739Z | Info | Started LSP server in 0.08s +2024-08-20T12:39:29.338150Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Tx/Body.hs +2024-08-20T12:39:29.338717Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-20T12:39:29.885214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-20T12:39:31.055725Z | Info | Load cabal cradle using single file +2024-08-20T12:39:32.051054Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-d69572380fd97c449f546110fb1b3a02 cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT42210-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/bin/ghc-9.6.5 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.6.5/lib/ghc-9.6.5/lib +2024-08-20T12:39:35.466756Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-cc3e0d6750e2c384d753830f3552dc9ecad6ee90 +2024-08-20T12:39:35.473306Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-20T12:40:28.035621Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:41:28.056454Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:42:28.084624Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:43:28.094416Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:44:28.108221Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:45:28.113914Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:46:28.116579Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:47:28.148599Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:48:28.190678Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:49:28.233937Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:50:28.291652Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:51:28.295798Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:52:28.346090Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:53:28.406643Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:54:28.420574Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:55:28.481180Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:56:28.533326Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:57:28.593915Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:58:28.617694Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T12:59:28.677473Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:00:28.737477Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:01:28.797635Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:02:28.836299Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:03:28.847699Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:04:28.907438Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:05:28.967609Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:06:29.028355Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:07:29.061899Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:08:29.101773Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:09:29.151078Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:10:29.211615Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:11:29.271440Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:12:29.331498Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:13:29.391929Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:14:29.452650Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:15:29.512561Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:16:29.572542Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:17:29.582768Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:18:29.584676Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:19:29.594634Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:20:29.601147Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:21:29.617881Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:22:29.652562Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:23:29.713342Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:24:29.727706Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:25:29.788453Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:26:29.844562Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:27:29.905391Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:28:29.966181Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:29:30.004627Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:30:30.065478Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:31:30.116580Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:32:30.177330Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:33:30.228551Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:34:30.289284Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:35:30.320563Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:36:30.381504Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:37:30.441915Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:38:30.475490Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:39:30.536182Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:40:30.586956Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:41:30.647126Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:42:30.707988Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:43:30.768551Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:44:30.829435Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:45:30.890134Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:46:30.950478Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:47:31.011221Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:48:31.071760Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:49:31.120746Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:50:31.181318Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:51:31.241717Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:52:31.302296Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:53:31.358560Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:54:31.419205Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:55:31.459166Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:56:31.515346Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:57:31.548983Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:58:31.580194Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T13:59:31.586818Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:00:31.646610Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:01:31.706708Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:02:31.766457Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:03:31.826563Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:04:31.886549Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:05:31.946566Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:06:32.006414Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:07:32.066911Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:08:32.127540Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:09:32.164442Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:10:32.224473Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:11:32.284859Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:12:32.344543Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:13:32.405007Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:14:32.465409Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:15:32.525804Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:16:32.585677Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:17:32.645398Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:18:32.705345Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:19:32.765500Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:20:32.780717Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:21:32.807780Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:22:32.834548Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:23:32.863629Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:24:32.924249Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:25:32.928499Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:26:32.941067Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:27:32.948455Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:28:33.009042Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:29:33.069620Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:30:33.099696Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:31:33.160341Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:32:33.176624Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:33:33.229409Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:34:33.268056Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:35:33.328425Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:36:33.364623Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:37:33.410607Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:38:33.470576Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:39:33.530427Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:40:33.541743Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:41:33.546029Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:42:33.588608Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:43:33.649221Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:44:33.675639Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:45:33.736273Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:46:33.796614Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:47:33.855806Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:48:33.894647Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:49:33.955313Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:50:33.988363Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:51:34.033579Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:52:34.093388Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:53:34.124587Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:54:34.148486Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:55:34.208382Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:56:34.246539Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:57:34.278751Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:58:34.338593Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T14:59:34.398528Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:00:34.413323Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:01:34.433523Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:02:34.441433Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:03:34.453412Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:04:34.513383Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:05:34.573489Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:06:34.633381Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:07:34.693406Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:08:34.753453Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:09:34.813350Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:10:34.873399Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:11:34.933357Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:12:34.993865Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:13:35.054457Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:14:35.114359Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:15:35.174412Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:16:35.234349Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:17:35.294365Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:18:35.354352Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:19:35.414413Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:20:35.474336Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:21:35.534373Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:22:35.594364Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:23:35.654417Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:24:35.714900Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:25:35.774401Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:26:35.834337Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:27:35.894434Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:28:35.954463Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:29:36.014635Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:30:36.074475Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:31:36.134353Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:32:36.191756Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:33:36.234242Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:34:36.244704Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:35:36.305550Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:36:36.335371Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:37:36.340593Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:38:36.347671Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:39:36.408220Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:40:36.412608Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:41:36.473193Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:42:36.533780Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:43:36.591440Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:44:36.651877Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:45:36.652568Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:46:36.713110Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:47:36.764095Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:48:36.824686Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:49:36.878828Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:50:36.938404Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:51:36.998488Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:52:37.058393Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:53:37.063571Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:54:37.123409Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:55:37.183406Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:56:37.212988Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:57:37.272518Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:58:37.315538Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T15:59:37.374293Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:00:37.388623Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:01:37.406811Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:02:37.466505Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:03:37.527310Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:04:37.587514Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:05:37.641686Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:06:37.702394Z | Info | Live bytes: 467.60MB Heap size: 1737.49MB +2024-08-20T16:07:37.763977Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:08:37.823421Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:09:37.883531Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:10:37.944133Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:11:38.004348Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:12:38.059690Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:13:38.113589Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:14:38.173459Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:15:38.206636Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:16:38.266414Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:17:38.327008Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:18:38.341717Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:19:38.355972Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:20:38.396495Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:21:38.457066Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:22:38.517553Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:23:38.565068Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:24:38.625692Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:25:38.644751Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:26:38.705305Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:27:38.724571Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:28:38.732589Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:29:38.766390Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:30:38.826414Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:31:38.860722Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:32:38.868620Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:33:38.921589Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:34:38.974851Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:35:39.028455Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:36:39.089095Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:37:39.149699Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:38:39.172602Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:39:39.220653Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:40:39.223865Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:41:39.231744Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:42:39.288898Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:43:39.316983Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:44:39.347194Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:45:39.394689Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:46:39.398320Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:47:39.459068Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:48:39.508571Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:49:39.527977Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:50:39.564564Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:51:39.595671Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:52:39.656442Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:53:39.663657Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:54:39.724426Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:55:39.785233Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:56:39.846005Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:57:39.848120Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:58:39.894633Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T16:59:39.933297Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:00:39.989902Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:01:40.050676Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:02:40.111404Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:03:40.139744Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:04:40.200462Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:05:40.260928Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:06:40.305293Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:07:40.365436Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:08:40.425326Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:09:40.467599Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:10:40.527508Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:11:40.554195Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:12:40.614569Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:13:40.675082Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:14:40.697519Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:15:40.716798Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:16:40.776451Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:17:40.836336Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:18:40.896479Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:19:40.956439Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:20:40.970347Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:21:41.030837Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:22:41.091394Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:23:41.123166Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:24:41.136675Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:25:41.139577Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:26:41.199546Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:27:41.253566Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:28:41.261363Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:29:41.321368Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:30:41.381906Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:31:41.441919Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:32:41.451340Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:33:41.511942Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:34:41.539699Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:35:41.600214Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:36:41.660652Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:37:41.720464Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:38:41.780402Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:39:41.840918Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:40:41.894644Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:41:41.954363Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:42:42.011490Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:43:42.072099Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:44:42.085458Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:45:42.146107Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:46:42.186464Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:47:42.247103Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:48:42.307673Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:49:42.313959Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:50:42.374504Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:51:42.434542Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:52:42.495207Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:53:42.555856Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:54:42.586535Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:55:42.589377Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:56:42.634483Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:57:42.695058Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:58:42.755714Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T17:59:42.776826Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:00:42.837352Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:01:42.897818Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:02:42.958449Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:03:42.992764Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:04:43.053295Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:05:43.094770Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:06:43.113842Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:07:43.139633Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:08:43.180562Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:09:43.241045Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:10:43.284628Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:11:43.311523Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:12:43.372071Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:13:43.432618Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:14:43.493076Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:15:43.553344Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:16:43.614010Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:17:43.636575Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:18:43.697133Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:19:43.757431Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:20:43.817507Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:21:43.877676Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:22:43.938342Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:23:43.998401Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:24:44.059061Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:25:44.107009Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:26:44.140729Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:27:44.200683Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:28:44.223145Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:29:44.276654Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:30:44.337271Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:31:44.398020Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:32:44.458631Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:33:44.517304Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:34:44.562108Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:35:44.622623Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:36:44.683127Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:37:44.737459Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:38:44.786309Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:39:44.847158Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:40:44.863879Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:41:44.868420Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:42:44.917364Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:43:44.977336Z | Info | Live bytes: 481.37MB Heap size: 1737.49MB +2024-08-20T18:44:32.611725Z | Info | LSP: received shutdown +2024-08-20T18:44:32.613761Z | Error | Got EOF +2024-08-21 12:37:31.1710000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-21 12:37:31.1720000 [client] INFO Finding haskell-language-server +2024-08-21 12:37:31.1730000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:31.1730000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:31.1800000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-21 12:37:31.7860000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:31.7860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:31.7920000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-21 12:37:31.9180000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:31.9180000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:31.9260000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-21 12:37:32.0640000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:32.0640000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:32.0690000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-21 12:37:32.2220000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:32.2220000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:32.2300000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-21 12:37:32.2450000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:32.2450000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:32.2510000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-21 12:37:32.2670000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:32.2670000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:32.2760000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-21 12:37:32.2970000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-21 12:37:32.3440000 [client] INFO Checking for ghcup installation +2024-08-21 12:37:32.3440000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:37:32.3500000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-21 12:37:32.5070000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-21 12:37:32.5070000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-21 12:38:01.5650000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-21 12:38:01.8840000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-21 12:38:01.8840000 [client] INFO Checking for ghcup installation +2024-08-21 12:38:01.8850000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:38:01.8900000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-21 12:38:01.9760000 [client] INFO Checking for ghcup installation +2024-08-21 12:38:01.9760000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:38:01.9810000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-21 12:38:01.9970000 [client] INFO Checking for ghcup installation +2024-08-21 12:38:01.9970000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:38:02.0010000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-21 12:38:02.0140000 [client] INFO Checking for ghcup installation +2024-08-21 12:38:02.0140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:38:02.0190000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-21 12:38:02.0320000 [client] INFO Checking for ghcup installation +2024-08-21 12:38:02.0330000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-21 12:38:02.0370000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-21 12:38:02.1420000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-21 12:38:02.1430000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-21 12:38:02.1430000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-21 12:38:02.1430000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-21 12:38:02.1430000 [client] INFO server environment variables: +2024-08-21 12:38:02.1430000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-21 12:38:02.1430000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-21 12:38:02.1430000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-21 12:38:02.1440000 [client] INFO Starting language server +2024-08-21T12:38:14.077490Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-21T12:38:14.078994Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-21T12:38:14.079492Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-21T12:38:14.082731Z | Info | Logging heap statistics every 60.00s +2024-08-21T12:38:14.091863Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-21T12:38:14.092490Z | Info | Starting server +2024-08-21T12:38:14.108216Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-21T12:38:14.165657Z | Info | Started LSP server in 0.07s +2024-08-21T12:38:15.531000Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Genesis.hs +2024-08-21T12:38:15.531609Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-21T12:38:16.061172Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-21T12:38:17.227004Z | Info | Load cabal cradle using single file +2024-08-21T12:38:18.279414Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT660797-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-21T12:38:22.264659Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-4038d54d7016811a700b4ec46bf347dd42faf01c +2024-08-21T12:38:22.268574Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-21T12:39:14.125480Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:40:14.157880Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:41:14.218449Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:42:14.240737Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:43:14.301284Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:44:14.312690Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:45:14.372201Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:46:14.432841Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:47:14.493509Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:48:14.511938Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:49:14.572456Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:50:14.610494Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:51:14.626242Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:52:14.656455Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:53:14.687615Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:54:14.698433Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:55:14.758340Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:56:14.818896Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:57:14.879282Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:58:14.892068Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T12:59:14.937852Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T13:00:14.982514Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T13:01:15.042336Z | Info | Live bytes: 444.98MB Heap size: 1665.14MB +2024-08-21T13:01:51.206091Z | Info | LSP: received shutdown +2024-08-21T13:01:51.208236Z | Error | Got EOF +2024-08-22 15:54:10.9130000 [client] INFO Writing client log to file /home/jordan/Repos/Work/intersect-mbo/cardano-api/hls.log +2024-08-22 15:54:10.9230000 [client] INFO Finding haskell-language-server +2024-08-22 15:54:10.9250000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:10.9250000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:10.9320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose upgrade' in cwd '/home/jordan' +2024-08-22 15:54:11.5400000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:11.5400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:11.5460000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-22 15:54:11.6770000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:11.6770000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:11.6820000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t cabal -c installed -r' in cwd '/home/jordan' +2024-08-22 15:54:11.7890000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:11.7900000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:11.7940000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t stack -c installed -r' in cwd '/home/jordan' +2024-08-22 15:54:11.9140000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:11.9140000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:11.9220000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-22 15:54:11.9400000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:11.9400000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:11.9440000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis cabal 3.10.3.0' in cwd '/home/jordan' +2024-08-22 15:54:11.9610000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:11.9610000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:11.9670000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis stack 2.13.1' in cwd '/home/jordan' +2024-08-22 15:54:11.9910000 [client] INFO Executing 'ghc --numeric-version' in cwd '/home/jordan' +2024-08-22 15:54:12.0190000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:12.0190000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:12.0250000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --install' in cwd '/home/jordan' +2024-08-22 15:54:12.1300000 [client] INFO Working out the project GHC version. This might take a while... +2024-08-22 15:54:12.1310000 [client] INFO Executing 'haskell-language-server-wrapper --project-ghc-version' in cwd '/home/jordan/Repos/Work/intersect-mbo/cardano-api' +2024-08-22 15:54:33.6420000 [client] INFO The GHC version for the project or file: 9.8.2 +2024-08-22 15:54:34.1370000 [client] INFO Platform constants: Linux_UnknownLinux, A_64 +2024-08-22 15:54:34.1380000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:34.1380000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:34.1420000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose list -t hls -c installed -r' in cwd '/home/jordan' +2024-08-22 15:54:34.2270000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:34.2270000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:34.2320000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis bindir' in cwd '/home/jordan' +2024-08-22 15:54:34.2490000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:34.2490000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:34.2550000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis hls 2.9.0.1' in cwd '/home/jordan' +2024-08-22 15:54:34.2690000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:34.2690000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:34.2730000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose whereis ghc 9.8.2' in cwd '/home/jordan' +2024-08-22 15:54:34.2860000 [client] INFO Checking for ghcup installation +2024-08-22 15:54:34.2860000 [client] INFO Trying to find the ghcup executable in: /home/jordan/.ghcup/bin/ghcup +2024-08-22 15:54:34.2910000 [client] INFO Executing '/home/jordan/.ghcup/bin/ghcup --no-verbose run --hls 2.9.0.1 --cabal 3.10.3.0 --stack 2.13.1 --ghc 9.8.2 --install' in cwd '/home/jordan' +2024-08-22 15:54:34.3750000 [client] INFO Activating the language server in working dir: /home/jordan/Repos/Work/intersect-mbo/cardano-api (the workspace folder) +2024-08-22 15:54:34.3760000 [client] INFO run command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-22 15:54:34.3760000 [client] INFO debug command: /home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1/haskell-language-server-wrapper --lsp -l hls.log +2024-08-22 15:54:34.3760000 [client] INFO server cwd: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-22 15:54:34.3760000 [client] INFO server environment variables: +2024-08-22 15:54:34.3760000 [client] INFO PKG_CONFIG_PATH=/usr/local/opt/cardano/lib/pkgconfig:$PKG_CONFIG_PATH +2024-08-22 15:54:34.3760000 [client] INFO LD_LIBRARY_PATH=/usr/local/opt/cardano/lib:$LD_LIBRARY_PATH +2024-08-22 15:54:34.3760000 [client] INFO PATH=/home/jordan/.ghcup/tmp/ghcup-ghc-9.8.2_cabal-3.10.3.0_hls-2.9.0.1_stack-2.13.1:/home/jordan/.cabal/bin:/home/jordan/.ghcup/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/home/jordan/.cargo/bin:/home/jordan/.local/bin:/home/jordan/.nix-profile/bin:/nix/var/nix/profiles/default/bin:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/usr/local/games:/snap/bin:/snap/bin +2024-08-22 15:54:34.3770000 [client] INFO Starting language server +2024-08-22T15:54:45.547300Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-22T15:54:45.549374Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-22T15:54:45.549775Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T15:54:45.554386Z | Info | Logging heap statistics every 60.00s +2024-08-22T15:54:45.562411Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T15:54:45.562813Z | Info | Starting server +2024-08-22T15:54:45.577998Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-22T15:54:45.632467Z | Info | Started LSP server in 0.07s +2024-08-22T15:54:46.976400Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Genesis.hs +2024-08-22T15:54:46.976987Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-22T15:54:47.553163Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T15:54:48.393220Z | Info | Load cabal cradle using single file +2024-08-22T15:54:49.341417Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT67551-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-22T15:54:54.984253Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-4038d54d7016811a700b4ec46bf347dd42faf01c +2024-08-22T15:54:54.990166Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-22T15:55:45.578504Z | Info | Live bytes: 434.90MB Heap size: 1862.27MB +2024-08-22T15:56:45.605974Z | Info | Live bytes: 434.90MB Heap size: 1862.27MB +2024-08-22T15:56:50.898101Z | Info | LSP: received shutdown +2024-08-22T15:56:50.900257Z | Error | Got EOF +2024-08-22T15:57:27.011678Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-22T15:57:27.014008Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-22T15:57:27.014744Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T15:57:27.023389Z | Info | Logging heap statistics every 60.00s +2024-08-22T15:57:27.046254Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T15:57:27.047268Z | Info | Starting server +2024-08-22T15:57:27.050866Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-22T15:57:27.105379Z | Info | Started LSP server in 0.06s +2024-08-22T15:57:33.403516Z | Info | LSP: received shutdown +2024-08-22T15:57:33.406201Z | Info | Reactor thread stopped +2024-08-22T15:57:33.411854Z | Error | Got EOF +2024-08-22T15:58:06.738032Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-22T15:58:06.739623Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-22T15:58:06.739954Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T15:58:06.743783Z | Info | Logging heap statistics every 60.00s +2024-08-22T15:58:06.760620Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T15:58:06.761412Z | Info | Starting server +2024-08-22T15:59:06.804790Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:00:06.865393Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:01:06.925124Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:02:06.985506Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:03:07.044132Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:04:07.104593Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:05:07.165273Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:06:07.225747Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:07:07.286175Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:08:07.346606Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:09:07.407016Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:10:07.467556Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:11:07.528247Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:12:07.588740Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:13:07.649355Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:14:07.704124Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:15:07.716159Z | Info | Live bytes: 0.00MB Heap size: 0.00MB +2024-08-22T16:15:39.130600Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-22T16:15:39.166147Z | Info | Started LSP server in 17m32s +2024-08-22T16:15:44.997172Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Tx.hs +2024-08-22T16:15:44.998703Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-22T16:15:45.549981Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:15:45.550647Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:15:46.561650Z | Info | Load cabal cradle using single file +2024-08-22T16:15:47.526828Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT73364-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-22T16:15:53.076734Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-c7eb27b98b6004130b949a9fd3373bda06ca7249 +2024-08-22T16:15:53.080496Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-22T16:16:04.914448Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:04.914532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:07.719421Z | Info | Live bytes: 701.28MB Heap size: 2652.90MB +2024-08-22T16:16:10.741574Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:10.896221Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:11.135264Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:11.424559Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:11.424655Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:11.726218Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:14.187632Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:14.187759Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:14.979091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:14.979121Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:15.602713Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:15.602953Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:17.084592Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:17.508955Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:18.036110Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:18.036115Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:18.144596Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:31.824092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:31.824684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:40.577302Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:40.577384Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:41.732814Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:41.892175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:41.892175Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:42.333667Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:42.503749Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:42.812919Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:42.813236Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:43.406464Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:43.406532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:44.785721Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:45.262866Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:45.262991Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:45.663022Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:45.770949Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:45.972968Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:46.053759Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:46.145146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:46.145146Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:46.157788Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:46.244891Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:46.623117Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:46.732362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:46.732509Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:46.848448Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:47.114394Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:47.204512Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T16:16:47.282277Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:47.282361Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:48.740437Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:48.740541Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:49.192941Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:16:49.873711Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:16:49.873714Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:07.736835Z | Info | Live bytes: 665.70MB Heap size: 2959.08MB +2024-08-22T16:17:36.082346Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:36.082352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:36.869354Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:37.016835Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:37.286449Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:37.551640Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:37.551787Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:38.116572Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:38.865093Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:43.476495Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:43.476552Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:46.842251Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:46.842317Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:49.311405Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:49.311996Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:50.168282Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:50.168435Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:51.193098Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:51.433962Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:51.586350Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:51.966651Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:51.966658Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:52.406914Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:53.089924Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:17:57.887019Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:57.887366Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:58.752096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:17:58.752217Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:00.258833Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:00.258998Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:01.621560Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:01.621636Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:02.423176Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:02.423239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:03.422550Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:03.422777Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:04.530147Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:18:05.451215Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:05.451362Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:07.739080Z | Info | Live bytes: 1138.29MB Heap size: 2959.08MB +2024-08-22T16:18:09.835096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:09.835190Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:20.685801Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:20.685803Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:20.848426Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:18:21.001503Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:18:21.262209Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:18:21.530096Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:21.530120Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:18:22.142998Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:18:22.916706Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:19:07.746218Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:20:07.747358Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:21:07.760966Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:22:07.820453Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:23:07.880206Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:24:07.940994Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:25:07.948268Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:26:07.971450Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:27:07.980114Z | Info | Live bytes: 1232.29MB Heap size: 2959.08MB +2024-08-22T16:27:20.246663Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:27:20.246684Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:27:47.989327Z | Info | LSP: received shutdown +2024-08-22T16:27:47.990455Z | Error | Got EOF +2024-08-22T16:27:57.379339Z | Info | haskell-language-server version: 2.9.0.1 (GHC: 9.8.2) (PATH: /home/jordan/.ghcup/hls/2.9.0.1/lib/haskell-language-server-2.9.0.1/bin/haskell-language-server-9.8.2) +2024-08-22T16:27:57.380519Z | Info | Directory: /home/jordan/Repos/Work/intersect-mbo/cardano-api +2024-08-22T16:27:57.380853Z | Info | Starting (haskell-language-server) LSP server... + GhcideArguments {argsCommand = LSP, argsCwd = Nothing, argsShakeProfiling = Nothing, argsTesting = False, argsExamplePlugin = False, argsLogLevel = Info, argsLogFile = Just "hls.log", argsLogStderr = True, argsLogClient = False, argsThreads = 0, argsProjectGhcVersion = False} + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T16:27:57.384472Z | Info | Logging heap statistics every 60.00s +2024-08-22T16:27:57.392683Z | Info | Starting LSP server... + If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option! + PluginIds: [ pragmas-suggest + , pragmas-completion + , ghcide-code-actions-bindings + , ghcide-extend-import-action + , retrie + , stylish-haskell + , explicit-fields + , ghcide-code-actions-type-signatures + , ghcide-code-actions-fill-holes + , stan + , hlint + , changeTypeSignature + , ghcide-code-actions-imports-exports + , cabal-fmt + , notes + , ghcide-completions + , eval + , ghcide-type-lenses + , cabal + , overloaded-record-dot + , gadt + , LSPRecorderCallback + , importLens + , floskell + , codeRange + , class + , ormolu + , qualifyImportedNames + , ghcide-hover-and-symbols + , alternateNumberFormat + , rename + , splice + , moduleName + , semanticTokens + , fourmolu + , cabal-gild + , callHierarchy + , ghcide-core + , explicit-fixity + , pragmas-disable ] +2024-08-22T16:27:57.393144Z | Info | Starting server +2024-08-22T16:27:57.394828Z | Info | Registering IDE configuration: IdeConfiguration {workspaceFolders = fromList [NormalizedUri (-6511971617328114305) "file:///home/jordan/Repos/Work/intersect-mbo/cardano-api"], clientSettings = hashed Nothing} +2024-08-22T16:27:57.461126Z | Info | Started LSP server in 0.07s +2024-08-22T16:27:58.820016Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Experimental/Tx.hs +2024-08-22T16:27:58.820986Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-22T16:27:59.392673Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:00.369104Z | Info | Load cabal cradle using single file +2024-08-22T16:28:01.335851Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT111588-0 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-22T16:28:05.596227Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:07.060781Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-d8ef896745245be0f73706a51b009d08aa0b8ee4 +2024-08-22T16:28:07.064960Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-22T16:28:21.704239Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:22.395250Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:23.065092Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:23.653926Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:25.857872Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:28.215266Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:28.851401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:29.479225Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:33.161310Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:33.858439Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:34.409281Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:35.851704Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:42.980790Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:28:43.119354Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:28:43.485162Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:28:57.397059Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:29:57.457699Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:30:57.518237Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:31:57.519328Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:32:57.579967Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:33:57.640474Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:34:57.660340Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:35:57.721060Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:36:57.781771Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:37:57.842500Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:38:57.903227Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:39:57.963917Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:40:58.020339Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:41:58.080997Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:42:58.141717Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:43:58.187327Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:44:58.188260Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:45:58.208237Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:46:58.252272Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:47:58.281596Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:48:58.342119Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:49:58.353724Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:50:58.414357Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:51:58.422214Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:52:58.427020Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:53:58.460289Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:54:58.504766Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:55:58.565369Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:56:58.608903Z | Info | Live bytes: 662.53MB Heap size: 2435.84MB +2024-08-22T16:57:32.844307Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:57:58.620235Z | Info | Live bytes: 678.36MB Heap size: 2435.84MB +2024-08-22T16:58:00.160420Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:03.202434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:04.765347Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:05.325248Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:05.890271Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:13.767446Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:14.348187Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:19.630858Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:22.647542Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:51.569150Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:58:51.808906Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:58:51.951207Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T16:58:52.348156Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T16:58:58.625466Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T16:59:58.676186Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:00:58.736583Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:01:58.754645Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:02:58.815029Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:03:58.875411Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:04:58.884094Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:05:58.932221Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:06:58.956228Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:07:58.988214Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:08:59.020227Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:09:59.080869Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:10:59.094659Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:11:59.155271Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:12:59.205213Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:13:59.265909Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:14:59.326621Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:15:59.387245Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:16:59.447208Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:17:59.452272Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:18:59.511988Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:19:59.572130Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:20:59.596261Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:21:59.606591Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:22:59.628335Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:23:59.651483Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:24:59.712097Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:25:59.772808Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:26:59.833183Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:27:59.868308Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:28:59.911949Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:29:59.943976Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:31:00.004216Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:32:00.064845Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:33:00.125512Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:34:00.186208Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:35:00.246142Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:36:00.306167Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:37:00.366115Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:38:00.413009Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:39:00.473123Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:40:00.533748Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:41:00.594232Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:42:00.638227Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:43:00.653393Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:44:00.664284Z | Info | Live bytes: 806.74MB Heap size: 2435.84MB +2024-08-22T17:44:12.782793Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:00.709084Z | Info | Live bytes: 826.13MB Heap size: 2435.84MB +2024-08-22T17:45:33.076697Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:39.499506Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:40.430273Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T17:45:40.920069Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:41.558396Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:42.490834Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:43.347149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:44.305407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:45.949114Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:48.789076Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:45:49.898533Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:00.711230Z | Info | Live bytes: 896.05MB Heap size: 2435.84MB +2024-08-22T17:46:07.838407Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:09.126020Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:15.670734Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:16.231363Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:16.817228Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:32.520570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:39.003871Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:41.071292Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:41.811080Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:42.504221Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:43.317621Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:43.887334Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:44.546491Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:47.541512Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:48.154623Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:49.269957Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:55.514851Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:56.117945Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:56.718352Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:57.268285Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:46:59.430948Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:00.713571Z | Info | Live bytes: 1031.53MB Heap size: 2435.84MB +2024-08-22T17:47:03.443106Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:05.454529Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:06.289642Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:07.416995Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:13.414646Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T17:47:13.674263Z | Warning | No plugin handles this "completionItem/resolve" request. +2024-08-22T17:47:13.901004Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:14.515516Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:15.083869Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:47.034959Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:56.824179Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:47:57.694826Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:48:00.148060Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:48:00.714488Z | Info | Live bytes: 1128.39MB Heap size: 2435.84MB +2024-08-22T17:48:00.715434Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:48:01.631401Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:48:02.141915Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:48:02.372320Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:48:02.526472Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:48:02.912210Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:49:00.761366Z | Info | Live bytes: 627.23MB Heap size: 2765.09MB +2024-08-22T17:50:00.814271Z | Info | Live bytes: 627.23MB Heap size: 2765.09MB +2024-08-22T17:50:59.176214Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:51:00.816777Z | Info | Live bytes: 700.24MB Heap size: 2765.09MB +2024-08-22T17:51:02.464744Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:51:02.893876Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:51:04.163149Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:51:28.530404Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:51:29.257494Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:51:29.885006Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:51:30.449119Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:51:30.698871Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:51:30.876684Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:51:31.779502Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:51:32.715231Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:51:57.961608Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:51:59.525440Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:52:00.145727Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:52:00.819471Z | Info | Live bytes: 764.05MB Heap size: 2955.94MB +2024-08-22T17:52:02.691091Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:52:02.906095Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:03.123426Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:03.275235Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:03.609657Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:04.065022Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:04.120896Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:52:04.917504Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:05.713007Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:06.424405Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:06.424489Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:06.671586Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:06.671586Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:06.815230Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:06.815235Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:07.203350Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:07.203417Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:07.732280Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:52:07.741728Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:07.742189Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:08.607817Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:08.608009Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:09.539440Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:09.539525Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" ] +2024-08-22T17:52:26.576009Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:52:41.611698Z | Info | Cradle path: cardano-api/src/Cardano/Api/Experimental.hs +2024-08-22T17:52:41.612174Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-22T17:52:41.731376Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:41.731376Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" +2024-08-22T17:52:41.731465Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:42.019759Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:42.019850Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:42.153532Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:52:42.224866Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:42.224917Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:42.296954Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:42.296969Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:42.678801Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:42.678842Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:42.745628Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:42.745894Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:43.390867Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:43.391124Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:44.582500Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:44.582622Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:44.909155Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:44.909151Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:45.936163Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:45.936391Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:46.316771Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:52:46.316935Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:52:50.626406Z | Info | Load cabal cradle using single file +2024-08-22T17:52:51.633984Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT111588-195 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-22T17:53:00.827032Z | Info | Live bytes: 683.74MB Heap size: 3053.45MB +2024-08-22T17:53:05.020645Z | Info | Could not identify reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/src/Cardano/Api/Experimental.hs" +2024-08-22T17:53:05.020646Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:05.039845Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:05.039839Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:05.190577Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:05.190583Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:05.472878Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:53:05.557953Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:05.558030Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:05.710718Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:05.710723Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:05.901864Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:05.901903Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:06.095077Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:53:06.148390Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:06.148417Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:06.323373Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:06.323408Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:06.987502Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:06.987533Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:07.983968Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:07.983971Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:08.225030Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:08.225128Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:53:09.478875Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Eras.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs" ] +2024-08-22T17:53:09.479215Z | Info | Typechecking reverse dependencies for NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Experimental/Tx.hs": [ NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Convenience/Construction.hs" + , NormalizedFilePath "/home/jordan/Repos/Work/intersect-mbo/cardano-api/cardano-api/internal/Cardano/Api/Fees.hs" ] +2024-08-22T17:54:00.873776Z | Info | Live bytes: 867.32MB Heap size: 3053.45MB +2024-08-22T17:54:22.679136Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-aaabf35bab49cb97b1dedeb59b9c0fa5deed4d12 +2024-08-22T17:54:22.679487Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-aaabf35bab49cb97b1dedeb59b9c0fa5deed4d12 +2024-08-22T17:54:22.685033Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.2.0.0-inplace + , cardano-api-9.2.0.0-inplace-internal ] +2024-08-22T17:54:22.987141Z | Info | Cradle path: cardano-api/internal/Cardano/Api/Fees.hs +2024-08-22T17:54:22.987624Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-22T17:54:24.707849Z | Info | Load cabal cradle using single file +2024-08-22T17:54:25.845144Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba cardano-api:lib:internal + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT111588-200 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-22T17:54:29.858706Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-c7eb27b98b6004130b949a9fd3373bda06ca7249 +2024-08-22T17:54:29.863687Z | Info | Making new HscEnv. In-place unit ids: [cardano-api-9.2.0.0-inplace-internal] +2024-08-22T17:54:30.082980Z | Info | Cradle path: cardano-api/src/Cardano/Api/ChainSync/Client.hs +2024-08-22T17:54:30.083497Z | Info | invoking build tool to determine build flags (this may take some time depending on the cache) +2024-08-22T17:54:31.683383Z | Info | Load cabal cradle using single file +2024-08-22T17:54:32.764393Z | Info | cabal --builddir=/home/jordan/.cache/hie-bios/dist-cardano-api-421e1b3c108ffc95d1506cfadac1f678 v2-repl --with-compiler /home/jordan/.cache/hie-bios/wrapper-b54f81dea4c0e6d1626911c526bc4e36 --with-hc-pkg /home/jordan/.cache/hie-bios/ghc-pkg-b88342b269acd611f4601bef43a69dba lib:cardano-api + Environment Variables + HIE_BIOS_OUTPUT: /tmp/HIE_BIOS_OUTPUT111588-201 + HIE_BIOS_GHC: /home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/bin/ghc-9.8.2 + HIE_BIOS_GHC_ARGS: -B/home/jordan/.ghcup/ghc/9.8.2/lib/ghc-9.8.2/lib +2024-08-22T17:54:45.806698Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-aaabf35bab49cb97b1dedeb59b9c0fa5deed4d12 +2024-08-22T17:54:45.807023Z | Info | Interface files cache directory: /home/jordan/.cache/ghcide/cardano-api-9.2.0.0-inplace-internal-aaabf35bab49cb97b1dedeb59b9c0fa5deed4d12 +2024-08-22T17:54:45.811419Z | Info | Making new HscEnv. In-place unit ids: [ cardano-api-9.2.0.0-inplace + , cardano-api-9.2.0.0-inplace-internal ] +2024-08-22T17:55:00.876330Z | Info | Live bytes: 1109.48MB Heap size: 3321.89MB +2024-08-22T17:55:52.310816Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:55:53.301525Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T17:56:00.882195Z | Info | Live bytes: 1238.38MB Heap size: 3321.89MB +2024-08-22T17:57:00.940315Z | Info | Live bytes: 1238.38MB Heap size: 3321.89MB +2024-08-22T17:58:00.960739Z | Info | Live bytes: 1238.38MB Heap size: 3321.89MB +2024-08-22T17:59:01.021329Z | Info | Live bytes: 1238.38MB Heap size: 3321.89MB +2024-08-22T18:00:01.036304Z | Info | Live bytes: 1238.38MB Heap size: 3321.89MB +2024-08-22T18:01:01.096097Z | Info | Live bytes: 1238.38MB Heap size: 3321.89MB +2024-08-22T18:02:01.156788Z | Info | Live bytes: 1238.38MB Heap size: 3321.89MB +2024-08-22T18:02:58.896606Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T18:03:01.161293Z | Info | Live bytes: 1414.35MB Heap size: 3321.89MB +2024-08-22T18:03:01.762570Z | Warning | No plugin handles this "textDocument/semanticTokens/full" request. +2024-08-22T18:04:01.164217Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:05:01.224756Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:06:01.228304Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:07:01.260344Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:08:01.320908Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:09:01.381568Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:10:01.442131Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:11:01.502764Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:12:01.563195Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:13:01.623915Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:14:01.684447Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:15:01.744133Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:16:01.804129Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:17:01.864583Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:18:01.924132Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:19:01.984471Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:20:02.045010Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:21:02.105410Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:22:02.165023Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:23:02.225567Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:24:02.252157Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:25:02.304393Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:26:02.364813Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:27:02.425303Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:28:02.485253Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:29:02.545138Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:30:02.605884Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:31:02.666666Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:32:02.700248Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:33:02.760950Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:34:02.789144Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:35:02.844226Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:36:02.848404Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:37:02.908939Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:38:02.969578Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:39:03.030249Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:40:03.090813Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:41:03.151130Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:42:03.211658Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:43:03.272282Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:44:03.276123Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:45:03.336238Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:46:03.396818Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:47:03.457149Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:48:03.470172Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:49:03.530116Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:50:03.532250Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:51:03.592363Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:52:03.653091Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:53:03.713107Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:54:03.773050Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:55:03.833065Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:56:03.893143Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:57:03.953805Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:58:04.014138Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T18:59:04.074549Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:00:04.135002Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:01:04.165709Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:02:04.226436Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:03:04.287067Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:04:04.322291Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:05:04.382993Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:06:04.443634Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:07:04.448061Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:08:04.452289Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:09:04.484284Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:10:04.521888Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:11:04.582206Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:12:04.583034Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:13:04.596183Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:14:04.656265Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:15:04.716102Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:16:04.775783Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:17:04.836163Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:18:04.882973Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:19:04.942858Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:20:04.970262Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:21:04.973757Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:22:05.034287Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:23:05.094947Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:24:05.155411Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:25:05.215238Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:26:05.275106Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:27:05.335050Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:28:05.395198Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:29:05.455707Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:30:05.516300Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:31:05.558632Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:32:05.618219Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:33:05.678230Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:34:05.707779Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:35:05.768159Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:36:05.820297Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:37:05.880970Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:38:05.902159Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:39:05.962770Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:40:06.023832Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:41:06.084608Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:42:06.145318Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:43:06.205984Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:44:06.266766Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:45:06.320123Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:46:06.380253Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:47:06.440972Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:48:06.501485Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:49:06.561796Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:50:06.619381Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:51:06.620898Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:52:06.636415Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:53:06.696977Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:54:06.727409Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:55:06.737259Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:56:06.780038Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:57:06.807990Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:58:06.837300Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T19:59:06.897863Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:00:06.958268Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:01:07.018200Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:02:07.078731Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:03:07.126047Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:04:07.172353Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:05:07.232158Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:06:07.244398Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:07:07.305123Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:08:07.321051Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:09:07.358581Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:10:07.414162Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:11:07.472325Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:12:07.532889Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:13:07.540264Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:14:07.588668Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:15:07.628018Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:16:07.654339Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:17:07.660366Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:18:07.715022Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:19:07.732013Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:20:07.746218Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:21:07.794292Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:22:07.820387Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:23:07.848022Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:24:07.878025Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:25:07.894205Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:26:07.954741Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:27:07.963605Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:28:08.012328Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:29:08.071682Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:30:08.131078Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:31:08.155850Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:32:08.216345Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:33:08.276966Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:34:08.337472Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:35:08.398038Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:36:08.458601Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:37:08.519181Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:38:08.571550Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:39:08.572628Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:40:08.583943Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:41:08.644150Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:42:08.704879Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:43:08.730653Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:44:08.791172Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:45:08.851703Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:46:08.872632Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:47:08.933138Z | Info | Live bytes: 1450.15MB Heap size: 3321.89MB +2024-08-22T20:47:15.071263Z | Info | LSP: received shutdown +2024-08-22T20:47:15.073328Z | Error | Got EOF