{-# LINE 1 "./Data/NetCDF/Raw/Attributes.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Data.NetCDF.Raw.Attributes where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Data.Char
import Data.Word
import Data.NetCDF.Raw.Utils
nc_put_att_text :: Int -> Int -> String -> Int -> String -> IO Int
nc_put_att_text nc var name _ v = do
let ncid = fromIntegral nc
varid = fromIntegral var
ncsize = fromIntegral $ length v
let tv = map convChar v
withCString name $ \namep -> do
withCString tv $ \vp -> do
res <- nc_put_att_text'_ ncid varid namep ncsize vp
return $ fromIntegral res
where convChar c
| isAscii c = c
| otherwise = ' '
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_text"
nc_put_att_text'_ :: CInt -> CInt -> CString -> CULong
-> Ptr CChar -> IO CInt
nc_put_att :: Storable b =>
(CInt -> CInt -> CString -> CInt -> CULong -> Ptr b -> IO CInt)
-> (a -> b) -> Int -> Int -> String -> Int -> [a] -> IO Int
nc_put_att cfn conv nc var name xtype v = do
let ncid = fromIntegral nc
varid = fromIntegral var
ncxtype = fromIntegral xtype
ncsize = fromIntegral $ length v
let tv = map conv v
withCString name $ \namep -> do
withArray tv $ \vp -> do
res <- cfn ncid varid namep ncxtype ncsize vp
return $ fromIntegral res
nc_put_att_uchar :: Int -> Int -> String -> Int -> [Word8] -> IO Int
nc_put_att_uchar = nc_put_att nc_put_att_uchar'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_uchar"
nc_put_att_uchar'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CUChar -> IO CInt
nc_put_att_schar :: Int -> Int -> String -> Int -> [Word8] -> IO Int
nc_put_att_schar = nc_put_att nc_put_att_schar'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_schar"
nc_put_att_schar'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CChar -> IO CInt
nc_put_att_short :: Int -> Int -> String -> Int -> [Int] -> IO Int
nc_put_att_short = nc_put_att nc_put_att_short'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_short"
nc_put_att_short'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CShort -> IO CInt
nc_put_att_int :: Int -> Int -> String -> Int -> [Int] -> IO Int
nc_put_att_int = nc_put_att nc_put_att_int'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_int"
nc_put_att_int'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CInt -> IO CInt
nc_put_att_long :: Int -> Int -> String -> Int -> [Int] -> IO Int
nc_put_att_long = nc_put_att nc_put_att_long'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_long"
nc_put_att_long'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CLong -> IO CInt
nc_put_att_float :: Int -> Int -> String -> Int -> [Float] -> IO Int
nc_put_att_float = nc_put_att nc_put_att_float'_ realToFrac
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_float"
nc_put_att_float'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CFloat -> IO CInt
nc_put_att_double :: Int -> Int -> String -> Int -> [Double] -> IO Int
nc_put_att_double = nc_put_att nc_put_att_double'_ realToFrac
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_double"
nc_put_att_double'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CDouble -> IO CInt
nc_put_att_ushort :: Int -> Int -> String -> Int -> [Int] -> IO Int
nc_put_att_ushort = nc_put_att nc_put_att_ushort'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_ushort"
nc_put_att_ushort'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CUShort -> IO CInt
nc_put_att_uint :: Int -> Int -> String -> Int -> [Int] -> IO Int
nc_put_att_uint = nc_put_att nc_put_att_uint'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_uint"
nc_put_att_uint'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CUInt -> IO CInt
nc_put_att_longlong :: Int -> Int -> String -> Int -> [Int] -> IO Int
nc_put_att_longlong = nc_put_att nc_put_att_longlong'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_longlong"
nc_put_att_longlong'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CLLong -> IO CInt
nc_put_att_ulonglong :: Int -> Int -> String -> Int -> [Int] -> IO Int
nc_put_att_ulonglong = nc_put_att nc_put_att_ulonglong'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_put_att_ulonglong"
nc_put_att_ulonglong'_ :: CInt -> CInt -> CString -> CInt -> CULong
-> Ptr CULLong -> IO CInt
nc_inq_attname :: (Int) -> (Int) -> (Int) -> IO ((Int), (String))
nc_inq_attname a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
allocaName $ \a4' ->
nc_inq_attname'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
peekCString a4'>>= \a4'' ->
return (res', a4'')
{-# LINE 143 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_inq_att :: (Int) -> (Int) -> (String) -> IO ((Int), (Int), (Int))
nc_inq_att a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
C2HSImp.withCString a3 $ \a3' ->
alloca $ \a4' ->
alloca $ \a5' ->
nc_inq_att'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = fromIntegral res} in
peekIntConv a4'>>= \a4'' ->
peekIntConv a5'>>= \a5'' ->
return (res', a4'', a5'')
{-# LINE 148 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_inq_attid :: (Int) -> (Int) -> (String) -> IO ((Int), (Int))
nc_inq_attid a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
C2HSImp.withCString a3 $ \a3' ->
alloca $ \a4' ->
nc_inq_attid'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
peekIntConv a4'>>= \a4'' ->
return (res', a4'')
{-# LINE 152 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_inq_atttype :: (Int) -> (Int) -> (String) -> IO ((Int), (Int))
nc_inq_atttype a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
C2HSImp.withCString a3 $ \a3' ->
alloca $ \a4' ->
nc_inq_atttype'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
peekIntConv a4'>>= \a4'' ->
return (res', a4'')
{-# LINE 156 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_inq_attlen :: (Int) -> (Int) -> (String) -> IO ((Int), (Int))
nc_inq_attlen a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
C2HSImp.withCString a3 $ \a3' ->
alloca $ \a4' ->
nc_inq_attlen'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
peekIntConv a4'>>= \a4'' ->
return (res', a4'')
{-# LINE 160 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_copy_att :: (Int) -> (Int) -> (String) -> (Int) -> (Int) -> IO ((Int))
nc_copy_att a1 a2 a3 a4 a5 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
C2HSImp.withCString a3 $ \a3' ->
let {a4' = fromIntegral a4} in
let {a5' = fromIntegral a5} in
nc_copy_att'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 164 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_rename_att :: (Int) -> (Int) -> (String) -> (String) -> IO ((Int))
nc_rename_att a1 a2 a3 a4 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
C2HSImp.withCString a3 $ \a3' ->
C2HSImp.withCString a4 $ \a4' ->
nc_rename_att'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 168 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_del_att :: (Int) -> (Int) -> (String) -> IO ((Int))
nc_del_att a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
C2HSImp.withCString a3 $ \a3' ->
nc_del_att'_ a1' a2' a3' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 171 "./Data/NetCDF/Raw/Attributes.chs" #-}
nc_get_att :: Storable a =>
(CInt -> CInt -> CString -> Ptr a -> IO CInt)
-> (a -> b) -> Int -> Int -> String -> Int -> IO (Int, [b])
nc_get_att cfn conv nc var name cnt = do
let ncid = fromIntegral nc
varid = fromIntegral var
withCString name $ \namep -> do
allocaArray cnt $ \vp -> do
res <- cfn ncid varid namep vp
vs <- peekArray cnt vp
return $ (fromIntegral res, map conv vs)
nc_get_att_text :: Int -> Int -> String -> Int -> IO (Int, String)
nc_get_att_text ncid var name ip = do
(s, str) <- nc_get_att nc_get_att_text'_ (chr . fromIntegral) ncid var name ip
return (s, takeWhile (/='\NUL') str)
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_text"
nc_get_att_text'_ :: CInt -> CInt -> CString -> Ptr CChar -> IO CInt
nc_get_att_uchar :: Int -> Int -> String -> Int -> IO (Int, [CChar])
nc_get_att_uchar = nc_get_att nc_get_att_uchar'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_uchar"
nc_get_att_uchar'_ :: CInt -> CInt -> CString -> Ptr CUChar -> IO CInt
nc_get_att_schar :: Int -> Int -> String -> Int -> IO (Int, [CSChar])
nc_get_att_schar = nc_get_att nc_get_att_schar'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_schar"
nc_get_att_schar'_ :: CInt -> CInt -> CString -> Ptr CChar -> IO CInt
nc_get_att_short :: Int -> Int -> String -> Int -> IO (Int, [CShort])
nc_get_att_short = nc_get_att nc_get_att_short'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_short"
nc_get_att_short'_ :: CInt -> CInt -> CString -> Ptr CShort -> IO CInt
nc_get_att_int :: Int -> Int -> String -> Int -> IO (Int, [CInt])
nc_get_att_int = nc_get_att nc_get_att_int'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_int"
nc_get_att_int'_ :: CInt -> CInt -> CString -> Ptr CInt -> IO CInt
nc_get_att_long :: Int -> Int -> String -> Int -> IO (Int, [CLong])
nc_get_att_long = nc_get_att nc_get_att_long'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_long"
nc_get_att_long'_ :: CInt -> CInt -> CString -> Ptr CLong -> IO CInt
nc_get_att_float :: Int -> Int -> String -> Int -> IO (Int, [CFloat])
nc_get_att_float = nc_get_att nc_get_att_float'_ realToFrac
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_float"
nc_get_att_float'_ :: CInt -> CInt -> CString -> Ptr CFloat -> IO CInt
nc_get_att_double :: Int -> Int -> String -> Int -> IO (Int, [CDouble])
nc_get_att_double = nc_get_att nc_get_att_double'_ realToFrac
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_double"
nc_get_att_double'_ :: CInt -> CInt -> CString -> Ptr CDouble -> IO CInt
nc_get_att_ushort :: Int -> Int -> String -> Int -> IO (Int, [CUShort])
nc_get_att_ushort = nc_get_att nc_get_att_ushort'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_ushort"
nc_get_att_ushort'_ :: CInt -> CInt -> CString -> Ptr CUShort -> IO CInt
nc_get_att_uint :: Int -> Int -> String -> Int -> IO (Int, [CUInt])
nc_get_att_uint = nc_get_att nc_get_att_uint'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_uint"
nc_get_att_uint'_ :: CInt -> CInt -> CString -> Ptr CUInt -> IO CInt
nc_get_att_longlong :: Int -> Int -> String -> Int -> IO (Int, [CLLong])
nc_get_att_longlong = nc_get_att nc_get_att_longlong'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_longlong"
nc_get_att_longlong'_ :: CInt -> CInt -> CString -> Ptr CLLong -> IO CInt
nc_get_att_ulonglong :: Int -> Int -> String -> Int -> IO (Int, [CULLong])
nc_get_att_ulonglong = nc_get_att nc_get_att_ulonglong'_ fromIntegral
foreign import ccall safe "Data/NetCDF/Raw.chs.h nc_get_att_ulonglong"
nc_get_att_ulonglong'_ :: CInt -> CInt -> CString -> Ptr CULLong -> IO CInt
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_inq_attname"
nc_inq_attname'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_inq_att"
nc_inq_att'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CInt))))))
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_inq_attid"
nc_inq_attid'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_inq_atttype"
nc_inq_atttype'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_inq_attlen"
nc_inq_attlen'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_copy_att"
nc_copy_att'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_rename_att"
nc_rename_att'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Data/NetCDF/Raw/Attributes.chs.h nc_del_att"
nc_del_att'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))))