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

Description

This module provides the high-level bindings to the TREXIO library for wave function data. The HighLevel modules provides complete high-level bindings to the TREXIO and the function names are generated by stripping the trexio_ prefix from the C function names and converting to camel case. E.g. the C function trexio_read_rdm_2e_updn_cholesky is available as readRdm2eUpdnCholesky.

The high-level bindings abstract mainly over three aspects of the C- (and also Python-API):

Memory management is done by the Haskell garbage collector and no pointers need to be moved around. All multidimensional data is safely handled by the Array type or the CooArray type.

Error handling is done by throwing ExitCode exceptions in IO, i.e. you don't need to check for error codes manually. You may catch ExitCode exceptions via the usual mechanisms, however.

In the Python- and C-APIs, Mutlidimensional quantities require writing their size to another field, referenced by the TREXIO specification first. For example, see this example for Python in TREXIO:

import trexio
coord = [    # xyz coordinates in atomic units
    [0. , 0., -0.24962655],
    [0. , 2.70519714, 1.85136466],
    [0. , -2.70519714, 1.85136466]
]
with trexio.File("water.trexio", w,
                 back_end=trexio.TREXIO_HDF5) as f:
    trexio.write_nucleus_num(f, len(coord))
    trexio.write_nucleus_coord(f, coord)

This high-level API abstracts over this and automatically writes the size of the array to the corresponding field. Safety checks are employed to ensure, should the size already exist, that it is consistent with the array size and other arrays utilising the same size field. Should this safety check be violated, an the AttrAlreadyExists exception will be thrown, as the corresponding size field already exists and is inconsistent with the new size. Thus, the Haskell equivalent to this is:

import TREXIO
import Data.Massiv.Array as Massiv

coord <- Massiv.fromListsM Par
    [ [0. , 0., -0.24962655]
    , [0. , 2.70519714, 1.85136466]
    , [0. , -2.70519714, 1.85136466]
    ]
withTrexio "water.trexio" FileWrite Hdf5 $ \trexio ->
    writeNucleusCoord trexio coord
Synopsis

Basic Operations

data ExitCode #

Instances

Instances details
Enum ExitCode 
Instance details

Defined in TREXIO.Internal.Base

Exception ExitCode 
Instance details

Defined in TREXIO.Internal.Base

Generic ExitCode 
Instance details

Defined in TREXIO.Internal.Base

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Show ExitCode 
Instance details

Defined in TREXIO.Internal.Base

Eq ExitCode 
Instance details

Defined in TREXIO.Internal.Base

Ord ExitCode 
Instance details

Defined in TREXIO.Internal.Base

type Rep ExitCode 
Instance details

Defined in TREXIO.Internal.Base

type Rep ExitCode = D1 ('MetaData "ExitCode" "TREXIO.Internal.Base" "trexio-hs-0.1.0-inplace-trexio-internal" 'False) (((((C1 ('MetaCons "Failure" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Success" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvalidArg1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidArg2" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InvalidArg3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidArg4" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvalidArg5" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "End" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReadOnly" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Errno" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidID" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AllocationFailed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HasNot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidNum" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AttrAlreadyExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DSetAlreadyExists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OpenError" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LockError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnlockError" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "FileError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GroupReadError" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GroupWriteError" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ElemReadError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ElemWriteError" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "UnsafeArrayDim" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AttrMissing" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DSetMissing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BackEndMissing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidArg6" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "InvalidArg7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidArg8" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvalidStrLen" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IntSizeOverflow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SafeMode" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "InvalidElectronNum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidDeterminantNum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvalidState" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VersionParsingIssue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PhaseChange" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data Backend #

Constructors

Hdf5 
Text 
Invalid 
Auto 

Instances

Instances details
Enum Backend 
Instance details

Defined in TREXIO.Internal.Base

Show Backend 
Instance details

Defined in TREXIO.Internal.Base

Eq Backend 
Instance details

Defined in TREXIO.Internal.Base

Methods

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

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

Ord Backend 
Instance details

Defined in TREXIO.Internal.Base

data Trexio #

data FileMode #

Constructors

FileRead 
FileWrite 
FileUnsafe 

Instances

Instances details
Generic FileMode 
Instance details

Defined in TREXIO.Internal.Base

Associated Types

type Rep FileMode :: Type -> Type #

Methods

from :: FileMode -> Rep FileMode x #

to :: Rep FileMode x -> FileMode #

Show FileMode 
Instance details

Defined in TREXIO.Internal.Base

Eq FileMode 
Instance details

Defined in TREXIO.Internal.Base

Ord FileMode 
Instance details

Defined in TREXIO.Internal.Base

type Rep FileMode 
Instance details

Defined in TREXIO.Internal.Base

type Rep FileMode = D1 ('MetaData "FileMode" "TREXIO.Internal.Base" "trexio-hs-0.1.0-inplace-trexio-internal" 'False) (C1 ('MetaCons "FileRead" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FileWrite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileUnsafe" 'PrefixI 'False) (U1 :: Type -> Type)))

close :: (MonadIO m, MonadThrow m) => Trexio -> m () #

markSafety :: (MonadIO m, MonadThrow m) => Trexio -> m () #

newtype TrexioScheme Source #

The overall data structure TREXIO uses to represent a wave function as a JSON specification. A TREXIO scheme consists of multiple data groups and each data group has multiple fields. A field may require knowledge of other fields.

Instances

Instances details
FromJSON TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSON TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

Generic TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

Associated Types

type Rep TrexioScheme :: Type -> Type #

Show TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

Eq TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

Ord TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

Lift TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

lift :: Quote m => TrexioScheme -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TrexioScheme -> Code m TrexioScheme #

type Rep TrexioScheme Source # 
Instance details

Defined in TREXIO.Internal.TH

type Rep TrexioScheme = D1 ('MetaData "TrexioScheme" "TREXIO.Internal.TH" "trexio-hs-0.1.0-inplace" 'True) (C1 ('MetaCons "TrexioScheme" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map GroupName Group))))

data GroupName Source #

The name of a data group, e.g. ao for atomic orbitals, basis for basis functions, etc.

Instances

Instances details
FromJSONKey GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSONKey GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

Generic GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

Associated Types

type Rep GroupName :: Type -> Type #

Show GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

Eq GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

Ord GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

Lift GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

lift :: Quote m => GroupName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => GroupName -> Code m GroupName #

type Rep GroupName Source # 
Instance details

Defined in TREXIO.Internal.TH

type Rep GroupName = D1 ('MetaData "GroupName" "TREXIO.Internal.TH" "trexio-hs-0.1.0-inplace" 'True) (C1 ('MetaCons "GroupName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype Group Source #

A data group is a record like data structure with named fields of different types. Each field may or may not be set, thus the Maybe type.

Constructors

Group (Map DataName Typ) 

Instances

Instances details
FromJSON Group Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSON Group Source # 
Instance details

Defined in TREXIO.Internal.TH

Generic Group Source # 
Instance details

Defined in TREXIO.Internal.TH

Associated Types

type Rep Group :: Type -> Type #

Methods

from :: Group -> Rep Group x #

to :: Rep Group x -> Group #

Show Group Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

Eq Group Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

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

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

Ord Group Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

compare :: Group -> Group -> Ordering #

(<) :: Group -> Group -> Bool #

(<=) :: Group -> Group -> Bool #

(>) :: Group -> Group -> Bool #

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

max :: Group -> Group -> Group #

min :: Group -> Group -> Group #

Lift Group Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

lift :: Quote m => Group -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Group -> Code m Group #

type Rep Group Source # 
Instance details

Defined in TREXIO.Internal.TH

type Rep Group = D1 ('MetaData "Group" "TREXIO.Internal.TH" "trexio-hs-0.1.0-inplace" 'True) (C1 ('MetaCons "Group" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map DataName Typ))))

data Typ Source #

The TREXIO type of a data field including sparsity, buffering, dimensionality etc.

Constructors

Dim Bool Length

A 32 integer but meant to represent the size in a given dimension. The Bool indicates if field can also be written

Int Length

A 32 bit integer

Float Bool Length

A double precision float. The Bool indicates whether this field is buffered

Str Length

A string with a given length

Idx Length

An index type

SparseFloat Length

Sparse array of floats

BitField Length

A bit field

Instances

Instances details
FromJSON Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSON Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

Generic Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

Associated Types

type Rep Typ :: Type -> Type #

Methods

from :: Typ -> Rep Typ x #

to :: Rep Typ x -> Typ #

Show Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

showsPrec :: Int -> Typ -> ShowS #

show :: Typ -> String #

showList :: [Typ] -> ShowS #

Eq Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

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

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

Ord Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

compare :: Typ -> Typ -> Ordering #

(<) :: Typ -> Typ -> Bool #

(<=) :: Typ -> Typ -> Bool #

(>) :: Typ -> Typ -> Bool #

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

max :: Typ -> Typ -> Typ #

min :: Typ -> Typ -> Typ #

Lift Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

lift :: Quote m => Typ -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Typ -> Code m Typ #

type Rep Typ Source # 
Instance details

Defined in TREXIO.Internal.TH

newtype Length Source #

TREXIO data fields are annotated with a length specification. This specification is a list of sizes along the dimensions of an $n$D array. An empty length specification refers to a scalar. A dimension may have a constant size or refer to another field that stores its size, see DimLength.

Constructors

Length [DimLength] 

Instances

Instances details
FromJSON Length Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSON Length Source # 
Instance details

Defined in TREXIO.Internal.TH

Generic Length Source # 
Instance details

Defined in TREXIO.Internal.TH

Associated Types

type Rep Length :: Type -> Type #

Methods

from :: Length -> Rep Length x #

to :: Rep Length x -> Length #

Show Length Source # 
Instance details

Defined in TREXIO.Internal.TH

Eq Length Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

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

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

Ord Length Source # 
Instance details

Defined in TREXIO.Internal.TH

Lift Length Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

lift :: Quote m => Length -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Length -> Code m Length #

type Rep Length Source # 
Instance details

Defined in TREXIO.Internal.TH

type Rep Length = D1 ('MetaData "Length" "TREXIO.Internal.TH" "trexio-hs-0.1.0-inplace" 'True) (C1 ('MetaCons "Length" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DimLength])))

data DimLength Source #

The size along a dimension of a field. It can be a constant or refer to a field that stores a scalar describing a length.

Instances

Instances details
FromJSON DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSON DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

Generic DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

Associated Types

type Rep DimLength :: Type -> Type #

Show DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

Eq DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

Ord DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

Lift DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

lift :: Quote m => DimLength -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DimLength -> Code m DimLength #

type Rep DimLength Source # 
Instance details

Defined in TREXIO.Internal.TH

data DataName Source #

The name of a data field, as specified by the TREXIO scheme. There is no guarantee that the name is a valid Haskell identifier. To ensure that, use the sanId function.

Instances

Instances details
FromJSON DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

FromJSONKey DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSON DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

ToJSONKey DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

Generic DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

Associated Types

type Rep DataName :: Type -> Type #

Methods

from :: DataName -> Rep DataName x #

to :: Rep DataName x -> DataName #

Show DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

Eq DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

Ord DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

Lift DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

Methods

lift :: Quote m => DataName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DataName -> Code m DataName #

type Rep DataName Source # 
Instance details

Defined in TREXIO.Internal.TH

type Rep DataName = D1 ('MetaData "DataName" "TREXIO.Internal.TH" "trexio-hs-0.1.0-inplace" 'True) (C1 ('MetaCons "DataName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

High Level Interface

scheme :: TrexioScheme Source #

The JSON specification of the code generator, that constructs the C-API and that this package binds to.

withTrexio :: (MonadMask m, MonadIO m) => FilePath -> FileMode -> Backend -> (Trexio -> m a) -> m a Source #

Work safely with a TREXIO file handle. Prefer over open and close.