Trick to have existential type work in this case?

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

On 2021-04-15 8:54 a.m., YueCompl via Haskell-Cafe wrote:
-- * Things not working managedArrayAsSeries::SomeManagedArray->IODynamic managedArrayAsSeries (SomeManagedArrayma)=do vec <-do SomeArraycap fp <-arrayAtTheMoment ma return $VS.unsafeFromForeignPtr0 fp cap letlen =return $VS.length vec rs i =return $vec VS.!i return $toDyn $Serieslen rs
That means you have this code fragment: arrayAtTheMoment ma
= \(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap
That means you have this function: \(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap Now you are violating the 1st restriction at https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/existent... https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/existent... There are two solutions. 1st solution: One more existential type. data Vec = forall a. (Typeable a, VS.Storable a) => Vec (VS.Vector a) Vec vec <- do SomeArray cap fp <- arrayAtTheMoment ma return (Vec (VS.unsafeFromForeignPtr0 fp cap)) 2nd solution: CPS transform. {-# language RankNTypes #-} {-# language BlockArguments #-} withSomeArray :: SomeArray -> (forall a. (Typeable a, VS.Storable a) => Int -> ForeignPtr a -> r) -> r withSomeArray (SomeArray i p) f = f i p sa <- arrayAtTheMoment ma withSomeArray sa \cap fp -> do let vec = VS.unsafeFromForeignPtr0 fp cap -- or if you prefer: vec <- return (VS.unsafeFromForeignPtr0 fp cap) len = return (VS.length vec) rs i = return (vec VS.! i) etc.

What a concise explanation and practical solutions! Thanks! With the hint from https://www.reddit.com/user/bss03/ https://www.reddit.com/user/bss03/ I've figured out the [1st solution](https://www.reddit.com/r/haskell/comments/mre9ha/trick_to_have_existential_t... https://www.reddit.com/r/haskell/comments/mre9ha/trick_to_have_existential_t...). And your 2nd solution really updated my knowledge about CPS, I used to assume some "continuation" always has to be passed around in CPS, now I know it can be used for nesting of scopes, and to have it naturally "return" back to outer scope. Thanks with best regards!
On 2021-04-16, at 02:27, Albert Y. C. Lai
wrote: On 2021-04-15 8:54 a.m., YueCompl via Haskell-Cafe wrote:
-- * 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
That means you have this code fragment:
arrayAtTheMoment ma
= \(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap That means you have this function:
\(SomeArray cap fp) -> return $ VS.unsafeFromForeignPtr0 fp cap Now you are violating the 1st restriction at https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/existent... https://downloads.haskell.org/ghc/latest/docs/html/users_guide/exts/existent... There are two solutions.
1st solution: One more existential type.
data Vec = forall a. (Typeable a, VS.Storable a) => Vec (VS.Vector a)
Vec vec <- do SomeArray cap fp <- arrayAtTheMoment ma return (Vec (VS.unsafeFromForeignPtr0 fp cap)) 2nd solution: CPS transform.
{-# language RankNTypes #-} {-# language BlockArguments #-}
withSomeArray :: SomeArray -> (forall a. (Typeable a, VS.Storable a) => Int -> ForeignPtr a -> r) -> r withSomeArray (SomeArray i p) f = f i p
sa <- arrayAtTheMoment ma withSomeArray sa \cap fp -> do let vec = VS.unsafeFromForeignPtr0 fp cap -- or if you prefer: vec <- return (VS.unsafeFromForeignPtr0 fp cap) len = return (VS.length vec) rs i = return (vec VS.! i) etc. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (2)
-
Albert Y. C. Lai
-
YueCompl