Skip to content

Commit 7095662

Browse files
committed
Support vector-0.13
Vector 0.13 changed the type roles on Data.Vector.Storable so that regular coerce can't be used to coerce the element types any more, instead we have to use unsafeCoerceVector. We need a little compatibility shim to support different versions of the vector package.
1 parent 743762f commit 7095662

File tree

5 files changed

+50
-20
lines changed

5 files changed

+50
-20
lines changed

glean.cabal.in

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -147,7 +147,7 @@ common deps
147147
contravariant ^>=1.5,
148148
text ^>=1.2.3.0,
149149
bytestring >=0.10.8.2 && <0.12,
150-
vector >=0.12.0.1 && <0.13,
150+
vector >=0.12.0.1 && <0.14,
151151
transformers ^>=0.5.6.2,
152152
network-uri ^>=2.6.1.0,
153153
stm ^>=2.5.0.0,
@@ -363,6 +363,7 @@ library util
363363
Glean.Util.TransitiveClosure
364364
Glean.Util.Trace
365365
Glean.Util.ValueBuffer
366+
Glean.Util.Vector
366367
Glean.Util.Warden
367368
build-depends:
368369
glean:stubs,

glean/db/Glean/Database/Write/Batch.hs

Lines changed: 14 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,6 @@ import Control.Trace (traceMsg)
1919
import qualified Data.ByteString as BS
2020
import qualified Data.HashMap.Strict as HashMap
2121
import Data.HashMap.Strict (HashMap)
22-
import Data.Coerce
2322
import Data.Default
2423
import Data.Int (Int64)
2524
import Data.IORef
@@ -48,11 +47,12 @@ import Glean.RTS.Foreign.Ownership as Ownership
4847
import Glean.RTS.Foreign.Stacked (stacked)
4948
import Glean.RTS.Foreign.Subst (Subst)
5049
import qualified Glean.RTS.Foreign.Subst as Subst
51-
import Glean.RTS.Types (Pid(..), Fid)
50+
import Glean.RTS.Types (Pid(..), Fid(..))
5251
import Glean.Types (Repo)
5352
import qualified Glean.Types as Thrift
5453
import Glean.Util.Metric
5554
import Glean.Util.Mutex
55+
import Glean.Util.Vector
5656
import qualified Glean.Write.Stats as Stats
5757

5858
writeContentFromBatch :: Thrift.Batch -> WriteContent
@@ -190,8 +190,10 @@ reallyWriteBatch env repo OpenDB{..} lock lookup writing original_size deduped
190190

191191
let
192192
commitOwnership = do
193-
owned <- mapM (coerce Subst.unsafeSubstIntervalsAndRelease subst)
194-
batch_owned
193+
let apply v = unsafeCoerceVector <$>
194+
Subst.unsafeSubstIntervalsAndRelease subst
195+
(unsafeCoerceVector v)
196+
owned <- mapM apply batch_owned
195197
Storage.addOwnership odbHandle lock owned
196198
deps <- mapM (substDependencies subst) batch_dependencies
197199
derivedOwners <-
@@ -285,8 +287,10 @@ deDupBatch env repo odb lookup writing original_size
285287
case maybe_deduped_batch of
286288
Nothing -> return dsubst
287289
Just deduped_batch -> do
288-
is <- mapM (coerce Subst.unsafeSubstIntervalsAndRelease dsubst)
289-
batch_owned
290+
let apply v = unsafeCoerceVector <$>
291+
Subst.unsafeSubstIntervalsAndRelease dsubst
292+
(unsafeCoerceVector v)
293+
is <- mapM apply batch_owned
290294
deps <- mapM (substDependencies dsubst) batch_dependencies
291295
forM_ maybeOwn $ \ownBatch ->
292296
Ownership.substDefineOwnership ownBatch dsubst
@@ -316,9 +320,10 @@ substDependencies
316320
substDependencies subst dmap = mapM substFD dmap
317321
where
318322
substFD (Thrift.FactDependencies facts deps) = do
319-
Thrift.FactDependencies
320-
<$> coerce (Subst.substVector subst) facts
321-
<*> coerce (Subst.substVector subst) deps
323+
Thrift.FactDependencies <$> apply facts <*> apply deps
324+
apply v =
325+
unsafeCoerceVector <$>
326+
Subst.substVector subst (unsafeCoerceVector v)
322327

323328
batchSize :: Thrift.Batch -> Word64
324329
batchSize = fromIntegral . BS.length . Thrift.batch_facts

glean/hs/Glean/RTS/Foreign/Define.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ module Glean.RTS.Foreign.Define
1717

1818
import Control.Exception
1919
import Control.Monad
20-
import Data.Coerce (coerce)
2120
import Data.Default
2221
import Data.Typeable
2322
import qualified Data.Vector.Storable as VS
@@ -35,6 +34,7 @@ import Glean.RTS.Foreign.Inventory (Inventory)
3534
import Glean.RTS.Foreign.Subst (Subst)
3635
import Glean.RTS.Types (Fid(..), Pid(..), invalidFid)
3736
import qualified Glean.Types as Thrift
37+
import Glean.Util.Vector
3838

3939
-- | A reference to a thing we can define facts in
4040
newtype Define = Define (Ptr Define)
@@ -108,7 +108,7 @@ defineBatch facts inventory batch DefineFlags{..} =
108108
withIds f
109109
| Just ids <- Thrift.batch_ids batch =
110110
if fromIntegral (VS.length ids) == Thrift.batch_count batch
111-
then VS.unsafeWith (coerce ids) f
111+
then VS.unsafeWith (unsafeCoerceVector ids) f
112112
else throwIO $
113113
Thrift.Exception "mismatch between count and ids.size in batch"
114114
| otherwise = f nullPtr

glean/hs/Glean/RTS/Foreign/Ownership.hsc

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,7 @@ import Glean.RTS.Foreign.Lookup
7070
import Glean.RTS.Foreign.Subst
7171
import Glean.RTS.Types
7272
import qualified Glean.Types as Thrift
73+
import Glean.Util.Vector
7374

7475
newtype UnitIterator = UnitIterator (Ptr UnitIterator)
7576
deriving(Storable)
@@ -213,14 +214,14 @@ addDerivedOwners base define (Pid pid) deps =
213214
define_ptr
214215
(fromIntegral pid)
215216
(fromIntegral $ length deps)
216-
p_facts_ptrs
217+
(castPtr p_facts_ptrs)
217218
p_facts_sizes
218-
p_deps_ptrs
219+
(castPtr p_deps_ptrs)
219220
p_deps_sizes
220221
where
221222
entry (Thrift.FactDependencies facts deps) f =
222-
VS.unsafeWith (coerce facts) $ \facts_ptr ->
223-
VS.unsafeWith (coerce deps) $ \deps_ptr -> do
223+
VS.unsafeWith facts $ \facts_ptr ->
224+
VS.unsafeWith deps $ \deps_ptr -> do
224225
let
225226
!num_facts = fromIntegral $ VS.length facts
226227
!num_deps = fromIntegral $ VS.length deps
@@ -286,8 +287,8 @@ getOwnershipSet ownership usetid =
286287
vec <- hsArrayStorable <$> peek (castPtr arr_ptr)
287288
let op | cop == (#const facebook::glean::rts::Or) = Or
288289
| cop == (#const facebook::glean::rts::And) = And
289-
| otherwise = error "unkonwn SetOp"
290-
return $ Just (op, coerce (vec :: VS.Vector Word32))
290+
| otherwise = error "unknown SetOp"
291+
return $ Just (op, unsafeCoerceVector (vec :: VS.Vector Word32))
291292
)
292293

293294
data OwnershipStats = OwnershipStats
@@ -349,8 +350,9 @@ newtype FactOwnership = FactOwnership
349350

350351
substOwnership :: Subst -> FactOwnership -> IO FactOwnership
351352
substOwnership subst (FactOwnership owned) = do
352-
owned' <- traverse (coerce $ unsafeSubstIntervalsAndRelease subst) owned
353-
return (FactOwnership owned')
353+
let apply x = unsafeCoerceVector <$>
354+
unsafeSubstIntervalsAndRelease subst (unsafeCoerceVector x)
355+
FactOwnership <$> traverse apply owned
354356

355357
unionOwnership :: [FactOwnership] -> FactOwnership
356358
unionOwnership =

glean/util/Glean/Util/Vector.hs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
{-
2+
Copyright (c) Meta Platforms, Inc. and affiliates.
3+
All rights reserved.
4+
5+
This source code is licensed under the BSD-style license found in the
6+
LICENSE file in the root directory of this source tree.
7+
-}
8+
9+
{-# LANGUAGE CPP #-}
10+
module Glean.Util.Vector (
11+
unsafeCoerceVector
12+
) where
13+
14+
import Data.Vector.Storable
15+
#if !MIN_VERSION_vector(0,13,0)
16+
import Data.Coerce
17+
#endif
18+
19+
#if !MIN_VERSION_vector(0,13,0)
20+
unsafeCoerceVector :: Coercible a b => Vector a -> Vector b
21+
unsafeCoerceVector = coerce
22+
#endif

0 commit comments

Comments
 (0)