module Data.Grib.Raw.Nearest
(
GribNearest(..)
, gribNearestNew
, gribNearestFind
, gribNearestFindMultiple
, gribNearestDelete
, withGribNearest
, GribNearestFlag(..)
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Control.Exception ( bracket )
import Foreign ( Ptr, Storable, alloca, allocaArray, fromBool
, peekArray, with, withArray, withMany )
import Foreign.C ( CSize )
import Control.Applicative
import Prelude
import Data.Grib.Raw.Handle
import Data.Grib.Raw.Marshal
newtype GribNearest = GribNearest (C2HSImp.Ptr (GribNearest)) deriving (Eq, Show)
data GribNearestFlag = GribNearestSameGrid
| GribNearestSameData
| GribNearestSamePoint
deriving (Eq,Show)
instance Enum GribNearestFlag where
succ GribNearestSameGrid = GribNearestSameData
succ GribNearestSameData = GribNearestSamePoint
succ GribNearestSamePoint = error "GribNearestFlag.succ: GribNearestSamePoint has no successor"
pred GribNearestSameData = GribNearestSameGrid
pred GribNearestSamePoint = GribNearestSameData
pred GribNearestSameGrid = error "GribNearestFlag.pred: GribNearestSameGrid has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from GribNearestSamePoint
fromEnum GribNearestSameGrid = 1
fromEnum GribNearestSameData = 2
fromEnum GribNearestSamePoint = 4
toEnum 1 = GribNearestSameGrid
toEnum 2 = GribNearestSameData
toEnum 4 = GribNearestSamePoint
toEnum unmatched = error ("GribNearestFlag.toEnum: Cannot match " ++ show unmatched)
gribNearestNew :: (GribHandle) -> IO ((GribNearest))
gribNearestNew a1 =
(withGribHandle) a1 $ \a1' ->
alloca $ \a2' ->
gribNearestNew'_ a1' a2' >>= \res ->
let {res' = id res} in
checkStatusPtr a2'>>
return (res')
gribNearestFind :: (GribNearest) -> (GribHandle) -> (Double) -> (Double) -> ([GribNearestFlag]) -> IO (([Double]), ([Double]), ([Double]), ([Double]), ([Int]))
gribNearestFind a1 a2 a3 a4 a5 =
let {a1' = id a1} in
(withGribHandle) a2 $ \a2' ->
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
let {a5' = fromFlagList a5} in
allocaArray4 $ \a6' ->
allocaArray4 $ \a7' ->
allocaArray4 $ \a8' ->
allocaArray4 $ \a9' ->
allocaArray4 $ \a10' ->
with4 $ \a11' ->
gribNearestFind'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
checkStatus res >>
peekRealArray4 a6'>>= \a6'' ->
peekRealArray4 a7'>>= \a7'' ->
peekRealArray4 a8'>>= \a8'' ->
peekRealArray4 a9'>>= \a9'' ->
peekIntegralArray4 a10'>>= \a10'' ->
return (a6'', a7'', a8'', a9'', a10'')
where allocaArray4 :: Storable a => (Ptr a -> IO b) -> IO b
allocaArray4 = allocaArray 4
peekIntegralArray4 = peekIntegralArray 4
peekRealArray4 = peekRealArray 4
with4 = with 4
gribNearestDelete :: (GribNearest) -> IO ((()))
gribNearestDelete a1 =
let {a1' = id a1} in
gribNearestDelete'_ a1' >>= \res ->
checkStatus res >>= \res' ->
return (res')
gribNearestFindMultiple :: GribHandle
-> Bool
-> [Double]
-> [Double]
-> IO ([Double], [Double], [Double], [Double], [Int])
gribNearestFindMultiple h lsm ilats ilons =
let lsm' = fromBool lsm
n = min (length ilats) (length ilons)
n' = fromIntegral n in
withGribHandle h $ \h' ->
withArray (map realToFrac ilats) $ \ilats' ->
withArray (map realToFrac ilons) $ \ilons' ->
withMany allocaArray (replicate 4 n) $ \[olats, olons, vals, dists] ->
allocaArray n $ \is -> do
cCall h' lsm' ilats' ilons' n' olats olons vals dists is >>= checkStatus
pack5 <$> fmap (map realToFrac) (peekArray n olats)
<*> fmap (map realToFrac) (peekArray n olons)
<*> fmap (map realToFrac) (peekArray n vals)
<*> fmap (map realToFrac) (peekArray n dists)
<*> fmap (map fromIntegral) (peekArray n is)
where cCall = grib_nearest_find_multiple
withGribNearest :: GribHandle -> (GribNearest -> IO a) -> IO a
withGribNearest h = bracket (gribNearestNew h) gribNearestDelete
foreign import ccall unsafe "Data/Grib/Raw/Nearest.chs.h grib_nearest_new"
gribNearestNew'_ :: ((C2HSImp.Ptr (GribHandle)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO (GribNearest))))
foreign import ccall unsafe "Data/Grib/Raw/Nearest.chs.h grib_nearest_find"
gribNearestFind'_ :: ((GribNearest) -> ((C2HSImp.Ptr (GribHandle)) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr CSize) -> (IO C2HSImp.CInt))))))))))))
foreign import ccall unsafe "Data/Grib/Raw/Nearest.chs.h grib_nearest_delete"
gribNearestDelete'_ :: ((GribNearest) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Data/Grib/Raw/Nearest.chs.h grib_nearest_find_multiple"
grib_nearest_find_multiple :: ((C2HSImp.Ptr (GribHandle)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (C2HSImp.CLong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))))))))))