hnetcdf-0.5.0.0: Haskell NetCDF library

Safe HaskellNone
LanguageHaskell98

Data.NetCDF

Description

Bindings to the Unidata NetCDF data access library.

As well as conventional low-level FFI bindings to the functions in the NetCDF library (in the Data.NetCDF.Raw modules), hnetcdf provides a higher-level Haskell interface (currently only for reading data). This higher-level interface aims to provide a "container polymorphic" view of NetCDF data allowing NetCDF variables to be read into Storable Vectors and Repa arrays easily.

For example:

import Data.NetCDF
import Foreign.C
import qualified Data.Vector.Storable as SV
...
type SVRet = IO (Either NcError (SV.Vector a))
...
  enc <- openFile "tst.nc"
  case enc of
    Right nc -> do
      eval <- get nc "varname" :: SVRet CDouble
      ...

gets the full contents of a NetCDF variable as a Storable Vector, while the following code reads the same variable (assumed to be three-dimensional) into a Repa array:

import Data.NetCDF
import Foreign.C
import qualified Data.Array.Repa as R
import qualified Data.Array.Repa.Eval as RE
import Data.Array.Repa.Repr.ForeignPtr (F)
...
type RepaRet3 a = IO (Either NcError (R.Array F R.DIM3 a))
...
  enc <- openFile "tst.nc"
  case enc of
    Right nc -> do
      eval <- get nc "varname" :: RepaRet3 CDouble
      ...
Synopsis

Documentation

class Storable a => NcStorable a where Source #

Class to collect the NetCDF FFI functions needed to read and write values in a NetCDF file for a given type.

Instances
NcStorable CChar Source # 
Instance details

Defined in Data.NetCDF.Storable

NcStorable CSChar Source # 
Instance details

Defined in Data.NetCDF.Storable

NcStorable CShort Source # 
Instance details

Defined in Data.NetCDF.Storable

NcStorable CInt Source # 
Instance details

Defined in Data.NetCDF.Storable

NcStorable CFloat Source # 
Instance details

Defined in Data.NetCDF.Storable

NcStorable CDouble Source # 
Instance details

Defined in Data.NetCDF.Storable

data IOMode #

Instances
Enum IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Eq IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Methods

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

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

Ord IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Read IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Ix IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

openFile :: FilePath -> NcIO (NcInfo NcRead) Source #

Open an existing NetCDF file for read-only access and read all metadata: the returned NcInfo value contains all the information about dimensions, variables and attributes in the file.

createFile :: NcInfo NcWrite -> NcIO (NcInfo NcWrite) Source #

Create a new NetCDF file, ready for write-only access. The NcInfo parameter contains all the information about dimensions, variables and attributes in the file.

syncFile :: NcInfo NcWrite -> IO () Source #

Sync a NetCDF file.

closeFile :: NcInfo a -> IO () Source #

Close a NetCDF file.

withReadFile :: FilePath -> (NcInfo NcRead -> IO r) -> (NcError -> IO r) -> IO r Source #

Bracket read-only file use: a little different from the standard withFile function because of error handling.

withCreateFile :: NcInfo NcWrite -> (NcInfo NcWrite -> IO r) -> (NcError -> IO r) -> IO r Source #

Bracket write-only file use: a little different from the standard withFile function because of error handling.

get1 :: NcStorable a => NcInfo NcRead -> NcVar -> [Int] -> NcIO a Source #

Read a single value from an open NetCDF file.

get :: (NcStorable a, NcStore s, NcStoreExtraCon s a) => NcInfo NcRead -> NcVar -> NcIO (s a) Source #

Read a whole variable from an open NetCDF file.

getA :: (NcStorable a, NcStore s, NcStoreExtraCon s a) => NcInfo NcRead -> NcVar -> [Int] -> [Int] -> NcIO (s a) Source #

Read a slice of a variable from an open NetCDF file.

getS :: (NcStorable a, NcStore s, NcStoreExtraCon s a) => NcInfo NcRead -> NcVar -> [Int] -> [Int] -> [Int] -> NcIO (s a) Source #

Read a strided slice of a variable from an open NetCDF file.

put1 :: NcStorable a => NcInfo NcWrite -> NcVar -> [Int] -> a -> NcIO () Source #

Write a single value to an open NetCDF file.

put :: (NcStorable a, NcStore s, NcStoreExtraCon s a) => NcInfo NcWrite -> NcVar -> s a -> NcIO () Source #

Write a whole variable to an open NetCDF file.

putA :: (NcStorable a, NcStore s, NcStoreExtraCon s a) => NcInfo NcWrite -> NcVar -> [Int] -> [Int] -> s a -> NcIO () Source #

Write a slice of a variable to an open NetCDF file.

putS :: (NcStorable a, NcStore s, NcStoreExtraCon s a) => NcInfo NcWrite -> NcVar -> [Int] -> [Int] -> [Int] -> s a -> NcIO () Source #

Write a strided slice of a variable to an open NetCDF file.

put1_String :: NcInfo NcWrite -> NcVar -> [Int] -> String -> NcIO () Source #

Write a single text value to an open NetCDF file.

coardsScale :: forall a b s. (NcStorable a, NcStorable b, FromNcAttr a, NcStore s, Real a, Fractional b, NcStoreExtraCon s a, NcStoreExtraCon s b) => NcVar -> s a -> s b Source #

Apply COARDS value scaling.