trexio-hs-0.1.0: Bindings to the TREXIO library for wave function data
CopyrightPhillip Seeber 2024
LicenseBSD-3-Clause
Maintainerphillip.seeber@uni-jena.de
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageGHC2021

TREXIO.CooArray

Description

 
Synopsis

Documentation

data CooArray r ix a Source #

A coordinate list array representation.

Instances

Instances details
Generic (CooArray r ix a) Source # 
Instance details

Defined in TREXIO.CooArray

Associated Types

type Rep (CooArray r ix a) :: Type -> Type #

Methods

from :: CooArray r ix a -> Rep (CooArray r ix a) x #

to :: Rep (CooArray r ix a) x -> CooArray r ix a #

(Show (Vector r a), Show (Vector r ix), Index ix, Show ix) => Show (CooArray r ix a) Source # 
Instance details

Defined in TREXIO.CooArray

Methods

showsPrec :: Int -> CooArray r ix a -> ShowS #

show :: CooArray r ix a -> String #

showList :: [CooArray r ix a] -> ShowS #

(Eq (Vector r a), Eq (Vector r ix), Eq ix) => Eq (CooArray r ix a) Source # 
Instance details

Defined in TREXIO.CooArray

Methods

(==) :: CooArray r ix a -> CooArray r ix a -> Bool #

(/=) :: CooArray r ix a -> CooArray r ix a -> Bool #

(Ord (Vector r a), Ord (Vector r ix), Ord ix) => Ord (CooArray r ix a) Source # 
Instance details

Defined in TREXIO.CooArray

Methods

compare :: CooArray r ix a -> CooArray r ix a -> Ordering #

(<) :: CooArray r ix a -> CooArray r ix a -> Bool #

(<=) :: CooArray r ix a -> CooArray r ix a -> Bool #

(>) :: CooArray r ix a -> CooArray r ix a -> Bool #

(>=) :: CooArray r ix a -> CooArray r ix a -> Bool #

max :: CooArray r ix a -> CooArray r ix a -> CooArray r ix a #

min :: CooArray r ix a -> CooArray r ix a -> CooArray r ix a #

type Rep (CooArray r ix a) Source # 
Instance details

Defined in TREXIO.CooArray

type Rep (CooArray r ix a) = D1 ('MetaData "CooArray" "TREXIO.CooArray" "trexio-hs-0.1.0-inplace" 'False) (C1 ('MetaCons "CooArray" 'PrefixI 'True) (S1 ('MetaSel ('Just "values_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector r a)) :*: (S1 ('MetaSel ('Just "coords_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector r ix)) :*: S1 ('MetaSel ('Just "cooSize_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Sz ix)))))

values :: CooArray r ix a -> Vector r a Source #

coords :: CooArray r ix a -> Vector r ix Source #

cooSize :: CooArray r ix a -> Sz ix Source #

mkCooArrayF :: (Foldable f, Index ix, Manifest r a, Manifest r ix, MonadThrow m, Stream r Ix1 ix) => Sz ix -> f (ix, a) -> m (CooArray r ix a) Source #

Make a CooArray from a list of coordinate-value pairs.

mkCooArray :: (MonadThrow m, Index ix, Size r, Stream r Ix1 ix) => Sz ix -> Vector r ix -> Vector r a -> m (CooArray r ix a) Source #

Make a CooArray from a indices and values.