This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
getEntityBodies :: Envelope -> [EntityBody] | |
getEntityBodies Envelope{..} = ePrimary : HashMap.elems eDenormalized | |
gatherMounts :: Envelope -> [Imq.ImqUpdateMount] | |
gatherMounts envelope = catMaybes $ map eUpdates $ getEntityBodies envelope | |
setupQueuesForEnvelope :: World m => CustomerId -> Envelope -> m () | |
setupQueuesForEnvelope cid envelope = do | |
RestIMQ.setupQueues cid $ gatherMounts envelope |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE MagicHash, RankNTypes, UnboxedTuples #-} | |
import GHC.Base | |
newtype Counter s a = Counter (STRep s a) | |
type STRep s a = Int# -> (# Int#, a #) | |
instance Functor (Counter s) where | |
fmap f (Counter m) = Counter $ \ s -> | |
case (m s) of { (# new_s, r #) -> |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE MagicHash, RankNTypes, UnboxedTuples #-} | |
import GHC.Base | |
newtype Counter s a = Counter (CRep s a) | |
type CRep s a = (# State# s, Int# #) -> (# State# s, Int#, a #) | |
instance Functor (Counter s) where | |
fmap f (Counter m) = Counter $ \ s -> | |
case (m s) of { (# new_s, n, r #) -> |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
grow :: (# State# RealWorld, Buffer# #) -> (# State# RealWorld, Buffer# #) | |
grow (# s0, (# _, size, cap, _ #) #) = | |
let newCap# = cap *# 2# in | |
let (IO iorep) = mallocForeignPtrBytes (I# newCap#) in | |
case iorep s0 of { | |
(# s1, fp@(ForeignPtr addr# _) #) -> (# s1, (# addr#, size, newCap#, fp #) #) } |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
s4YQ_ret() | |
{ Just s4YQ_info: | |
const 16777170; | |
const 32; | |
} | |
c5l5: | |
_s4YI::I64 = I64[Sp + 136] + I64[Sp + 128]; | |
_c5lG::I64 = I64[R1 + 7]; | |
_c5lH::I64 = I64[Sp + 144]; | |
foreign "ccall" |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
s4YQ_ret() | |
{ Just s4YQ_info: | |
const 16777170; | |
const 32; | |
} | |
c5l5: | |
_s4YI::I64 = I64[Sp + 136] + I64[Sp + 128]; | |
_c5lG::I64 = I64[R1 + 7]; | |
_c5lH::I64 = I64[Sp + 144]; | |
foreign "ccall" |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
vector :: (GVector.Vector v a, ToJson a) => v a -> JsonBuilder | |
vector !vec = JsonBuilder $ do | |
BB.appendChar8 '[' | |
when (GVector.length vec /= 0) $ do | |
unJsonBuilder $ appendJson (vec `GVector.unsafeIndex` 0) | |
GVector.forM_ vec $ \e -> do | |
BB.appendChar8 ',' | |
unJsonBuilder $ appendJson e | |
BB.appendChar8 ']' |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Running 1 benchmarks... | |
Benchmark json-bench: RUNNING... | |
warming up | |
estimating clock resolution... | |
mean is 793.1811 ns (640001 iterations) | |
found 1028891 outliers among 639999 samples (160.8%) | |
542409 (84.8%) low severe | |
486482 (76.0%) high severe | |
estimating cost of a clock call... | |
mean is 28.47098 ns (5 iterations) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Running 1 benchmarks... | |
Benchmark json-bench: RUNNING... | |
benchmarking list bool/bufferbuilder | |
time 1.621 ms (1.612 ms .. 1.628 ms) | |
1.000 R² (0.999 R² .. 1.000 R²) | |
mean 1.616 ms (1.610 ms .. 1.622 ms) | |
std dev 20.80 μs (15.53 μs .. 32.13 μs) | |
benchmarking list bool/aeson | |
time 2.821 ms (2.799 ms .. 2.841 ms) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Running 1 benchmarks... | |
Benchmark json-bench: RUNNING... | |
benchmarking vector/vector bool | |
time 1.846 ms (1.835 ms .. 1.857 ms) | |
0.999 R² (0.998 R² .. 1.000 R²) | |
mean 1.869 ms (1.857 ms .. 1.893 ms) | |
std dev 53.98 μs (35.62 μs .. 88.52 μs) | |
variance introduced by outliers: 16% (moderately inflated) | |
benchmarking vector/vector int |