File: File.hs

package info (click to toggle)
haskell-hdf5 1.8.14-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 876 kB
  • sloc: haskell: 2,515; ansic: 479; makefile: 6
file content (65 lines) | stat: -rw-r--r-- 2,112 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
{-# LANGUAGE CPP #-}
module Spec.File ( describeFile ) where

import Test.Hspec
-- import Test.QuickCheck

import qualified Data.ByteString.Char8 as BS
import qualified Bindings.HDF5.File as F
import qualified Data.Vector.Storable as SV

import Spec.Util

-- | Describe the H5F File interface
describeFile :: Spec
describeFile = do
  it "isHDF5 returns True for the test file" $ do
    isHdf5 <- withTestFile $ \path file -> do
      -- Flish file to disk
      F.flushFile file F.Global
      -- Return whether it is a valid HDF5 file
      F.isHDF5 (BS.pack path)
    isHdf5 `shouldBe` True

  it "getFileName reports correct filename" $ do
    (fn, path) <- withTestFile $ \path file -> do
      fn <- F.getFileName file
      return (fn, BS.pack path)
    fn `shouldBe` path

    {- TODO : create a group and mount it there so we can test something about it
    it "Allows mounting of one file in another" $ do
      x <- withTestFile $ \path file1 -> let callback file2 = do
                                               F.mountFile file1 (BS.pack "/") file2 Nothing
                                               return 42
                                         in withTestFile' callback
      x `shouldBe` 42
    -}


  it "global object count is zero initially" $ do
    count <- F.getFileObjCount Nothing True [F.All]
    count `shouldBe` 0

  around withTestFile' $ do
    it "test file has one file" $ \file -> do
      count <- F.getFileObjCount (Just file) True [F.Files]
      count `shouldBe` 1

    it "test file has no groups" $ \file -> do
      count <- F.getFileObjCount (Just file) True [F.Groups]
      count `shouldBe` 0

    it "test file has no datasets" $ \file -> do
      count <- F.getFileObjCount (Just file) True [F.Datasets]
      count `shouldBe` 0

    it "test file has 1 open object" $ \file -> do
      vec <- F.getOpenObjects (Just file)True [F.All]
      SV.length vec `shouldBe` 1

#if MIN_VERSION_hspec(2,2,5)
    xit "test file has no free space" $ \file -> do
      size <- F.getFileFreespace file
      size `shouldBe` 0  -- with hdf5 1.10.4 it returns 1248
#endif