
Dear Cafe, I believe there should exist some trick that I haven't learned, to have this compile: module PoC.Existential where import Data.Dynamic import qualified Data.Vector.Storable as VS import Foreign import Prelude -- * Necessary artifacts data Series a = Series { seriesLen :: IO Int, readSeries :: Int -> IO a } data SomeArray = forall a. (Typeable a, VS.Storable a) => SomeArray { arrayCap :: Int, arrayPtr :: ForeignPtr a } class ManagedArray t where arrayAtTheMoment :: t -> IO SomeArray data SomeManagedArray = forall t. (Typeable t, ManagedArray t) => SomeManagedArray t In following, I can confirm it works with the nested `do` block flattened (as shown later), but I really need it in the more complex real case, so please bear with me. -- * Things not working managedArrayAsSeries :: SomeManagedArray -> IO Dynamic managedArrayAsSeries (SomeManagedArray ma) = do vec <- do SomeArray cap fp <- arrayAtTheMoment ma return $ VS.unsafeFromForeignPtr0 fp cap let len = return $ VS.length vec rs i = return $ vec VS.! i return $ toDyn $ Series len rs The error: src/PoC/Existential.hs:36:5: error: • Couldn't match type ‘a’ with ‘a0’ ‘a’ is a rigid type variable bound by a pattern with constructor: SomeArray :: forall a. (Typeable a, Storable a) => Int -> ForeignPtr a -> SomeArray, in a pattern binding in a 'do' block at src/PoC/Existential.hs:35:5-20 Expected type: IO (VS.Vector a0) Actual type: IO (VS.Vector a) • In a stmt of a 'do' block: return $ VS.unsafeFromForeignPtr0 fp cap In a stmt of a 'do' block: vec <- do SomeArray cap fp <- arrayAtTheMoment ma return $ VS.unsafeFromForeignPtr0 fp cap In the expression: do vec <- do SomeArray cap fp <- arrayAtTheMoment ma return $ VS.unsafeFromForeignPtr0 fp cap let len = return $ VS.length vec rs i = return $ vec VS.! i return $ toDyn $ Series len rs • Relevant bindings include fp :: ForeignPtr a (bound at src/PoC/Existential.hs:35:19) | 36 | return $ VS.unsafeFromForeignPtr0 fp cap | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ While these more trivial things work as expected: -- * Things working managedArrayAsSeries' :: SomeManagedArray -> IO Dynamic managedArrayAsSeries' (SomeManagedArray ma) = do SomeArray cap fp <- arrayAtTheMoment ma let vec = VS.unsafeFromForeignPtr0 fp cap let len = return $ VS.length vec rs i = return $ vec VS.! i return $ toDyn $ Series len rs arrayAsSeries :: SomeArray -> Dynamic arrayAsSeries (SomeArray cap fp) = colAsSeries $ SomeColumn $ VS.unsafeFromForeignPtr0 fp cap arrayAsSeries' :: SomeArray -> Dynamic arrayAsSeries' (SomeArray cap fp) = do let vec = VS.unsafeFromForeignPtr0 fp cap len = return $ VS.length vec rs i = return $ vec VS.! i toDyn $ Series len rs data SomeColumn = forall a. (Typeable a, VS.Storable a) => SomeColumn (VS.Vector a) colAsSeries :: SomeColumn -> Dynamic colAsSeries (SomeColumn colVec) = toDyn $ Series len rs where len = return $ VS.length colVec rs i = return $ colVec VS.! i Please teach me the trick! Thanks with regards, Compl