What a concise explanation and practical solutions! Thanks!

With the hint from 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_type_work_in_this_case/guw5y80/?context=3).

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 <trebla@vex.net> 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/existential_quantification.html#restrictions

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.