{-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} module Torch.Internal.Managed.Type.C10Dict where import Foreign.C.String import Foreign.C.Types import Foreign import Torch.Internal.Type import Torch.Internal.Class import Torch.Internal.Cast import Torch.Internal.Objects import qualified Torch.Internal.Unmanaged.Type.C10Dict as Unmanaged import Control.Monad (forM) newC10Dict :: ForeignPtr IValue -> ForeignPtr IValue -> IO (ForeignPtr (C10Dict '(IValue,IValue))) newC10Dict :: ForeignPtr IValue -> ForeignPtr IValue -> IO (ForeignPtr (C10Dict '(IValue, IValue))) newC10Dict = forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y _cast2 Ptr IValue -> Ptr IValue -> IO (Ptr (C10Dict '(IValue, IValue))) Unmanaged.newC10Dict c10Dict_empty :: ForeignPtr (C10Dict '(IValue,IValue)) -> IO (CBool) c10Dict_empty :: ForeignPtr (C10Dict '(IValue, IValue)) -> IO CBool c10Dict_empty = forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y _cast1 Ptr (C10Dict '(IValue, IValue)) -> IO CBool Unmanaged.c10Dict_empty c10Dict_size :: ForeignPtr (C10Dict '(IValue,IValue)) -> IO (CSize) c10Dict_size :: ForeignPtr (C10Dict '(IValue, IValue)) -> IO CSize c10Dict_size = forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y _cast1 Ptr (C10Dict '(IValue, IValue)) -> IO CSize Unmanaged.c10Dict_size c10Dict_at :: ForeignPtr (C10Dict '(IValue,IValue)) -> ForeignPtr IValue -> IO (ForeignPtr IValue) c10Dict_at :: ForeignPtr (C10Dict '(IValue, IValue)) -> ForeignPtr IValue -> IO (ForeignPtr IValue) c10Dict_at = forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y _cast2 Ptr (C10Dict '(IValue, IValue)) -> Ptr IValue -> IO (Ptr IValue) Unmanaged.c10Dict_at c10Dict_insert :: ForeignPtr (C10Dict '(IValue,IValue)) -> ForeignPtr IValue -> ForeignPtr IValue -> IO () c10Dict_insert :: ForeignPtr (C10Dict '(IValue, IValue)) -> ForeignPtr IValue -> ForeignPtr IValue -> IO () c10Dict_insert = forall a ca x1 cx1 x2 cx2 y cy. (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) => (ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y _cast3 Ptr (C10Dict '(IValue, IValue)) -> Ptr IValue -> Ptr IValue -> IO () Unmanaged.c10Dict_insert c10Dict_toList :: ForeignPtr (C10Dict '(IValue,IValue)) -> IO [(ForeignPtr IValue,ForeignPtr IValue)] c10Dict_toList :: ForeignPtr (C10Dict '(IValue, IValue)) -> IO [(ForeignPtr IValue, ForeignPtr IValue)] c10Dict_toList ForeignPtr (C10Dict '(IValue, IValue)) obj = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr (C10Dict '(IValue, IValue)) obj forall a b. (a -> b) -> a -> b $ \Ptr (C10Dict '(IValue, IValue)) obj' -> do [(Ptr IValue, Ptr IValue)] v <- Ptr (C10Dict '(IValue, IValue)) -> IO [(Ptr IValue, Ptr IValue)] Unmanaged.c10Dict_toList Ptr (C10Dict '(IValue, IValue)) obj' :: IO [(Ptr IValue,Ptr IValue)] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) forM [(Ptr IValue, Ptr IValue)] v forall a b. (a -> b) -> a -> b $ \(Ptr IValue a,Ptr IValue b) -> do ForeignPtr IValue a' <- forall a b r. Castable a b => b -> (a -> IO r) -> IO r uncast Ptr IValue a forall (m :: * -> *) a. Monad m => a -> m a return ForeignPtr IValue b' <- forall a b r. Castable a b => b -> (a -> IO r) -> IO r uncast Ptr IValue b forall (m :: * -> *) a. Monad m => a -> m a return forall (m :: * -> *) a. Monad m => a -> m a return (ForeignPtr IValue a',ForeignPtr IValue b')