Skip to content

Commit 3f10d2e

Browse files
author
Philipp Kant
committed
Added test for dataFetchEquiv.
For illustration and testing.
1 parent 46d9dfd commit 3f10d2e

File tree

3 files changed

+149
-0
lines changed

3 files changed

+149
-0
lines changed

tests/EquivDataSource.hs

+103
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,103 @@
1+
{-# LANGUAGE FlexibleInstances #-}
2+
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4+
{-# LANGUAGE MultiParamTypeClasses #-}
5+
{-# LANGUAGE OverloadedStrings #-}
6+
{-# LANGUAGE StandaloneDeriving #-}
7+
{-# LANGUAGE TypeFamilies #-}
8+
9+
module EquivDataSource (
10+
MyData (..)
11+
, getSimilar
12+
, initGlobalState
13+
) where
14+
15+
import Haxl.Prelude
16+
import Prelude ()
17+
18+
import Haxl.Core
19+
import Haxl.Core.Monad (dataFetchEquiv)
20+
21+
import Control.Concurrent.MVar
22+
import Data.Hashable
23+
import Data.Map (Map)
24+
import qualified Data.Map as Map
25+
import Data.Typeable
26+
27+
-- Example data source using equivalent requests. The data source
28+
-- contains some numbers. Calling @getSimilar x@ queries if there is
29+
-- a number stored that is equal to @x@ modulo @7@. If so, this number
30+
-- is returned, if not, @x@ itself is stored (and returned).
31+
--
32+
-- This allows to perform a restricted class of write operations that
33+
-- can safely be reordered by Haxl.
34+
--
35+
-- This is a simplified version of the real-world usecase, which
36+
-- involves categorising pieces of data using some minhash-like method
37+
-- to measure similarity.
38+
39+
newtype MyKey = MyKey Int
40+
deriving (Eq, Ord, Hashable, Typeable, Show)
41+
newtype MyData = MyData Int
42+
deriving (Eq, Hashable, Typeable, Show)
43+
44+
data MyReq a where
45+
EnterOrRetrieveData :: MyData -> MyReq MyData
46+
RetrieveData :: MyKey -> MyReq MyData
47+
deriving Typeable
48+
49+
key :: MyData -> MyKey
50+
key (MyData x) = MyKey (x `mod` 7)
51+
52+
deriving instance Eq (MyReq a)
53+
deriving instance Show (MyReq a)
54+
instance Show1 MyReq where show1 = show
55+
instance Hashable (MyReq a) where
56+
hashWithSalt s (EnterOrRetrieveData x) = hashWithSalt s (0::Int, x)
57+
hashWithSalt s (RetrieveData x) = hashWithSalt s (1::Int, x)
58+
59+
instance StateKey MyReq where
60+
data State MyReq = MyState { myData :: MVar (Map MyKey MyData) }
61+
62+
instance DataSourceName MyReq where
63+
dataSourceName _ = "Datasource with equivalent requests"
64+
65+
instance DataSource u MyReq where
66+
fetch = myFetch
67+
68+
initGlobalState :: IO (State MyReq)
69+
initGlobalState = do
70+
myMVar <- newMVar Map.empty
71+
return (MyState myMVar)
72+
73+
myFetch :: State MyReq -> Flags -> u -> [BlockedFetch MyReq] -> PerformFetch
74+
myFetch state _flags _user bfs = SyncFetch $ mapM_ (fetch1 state) bfs
75+
76+
fetch1 :: State MyReq -> BlockedFetch MyReq -> IO ()
77+
fetch1 state (BlockedFetch (EnterOrRetrieveData val) m) =
78+
modifyMVar_ (myData state) $ \valMap ->
79+
case Map.lookup k valMap of
80+
Nothing ->
81+
putSuccess m val
82+
>> return (Map.insert k val valMap)
83+
Just val' ->
84+
putSuccess m val'
85+
>> return valMap
86+
where k = key val
87+
88+
fetch1 state (BlockedFetch (RetrieveData k) m) = do
89+
valMap <- readMVar (myData state)
90+
case Map.lookup k valMap of
91+
Just val -> putSuccess m val
92+
Nothing -> putFailure m (FetchError "This should not be possible.")
93+
94+
95+
getSimilar :: MyData -> (GenHaxl ()) MyData
96+
getSimilar =
97+
let equiv :: MyReq a -> MyReq a -> Bool
98+
equiv (EnterOrRetrieveData x) (EnterOrRetrieveData y) = key x == key y
99+
equiv _ _ = error "impossible"
100+
representative :: MyReq a -> MyReq a
101+
representative (EnterOrRetrieveData x) = RetrieveData (key x)
102+
representative _ = error "impossible"
103+
in dataFetchEquiv equiv representative . EnterOrRetrieveData

tests/Main.hs

+2
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ import DataCacheTest
88
#ifdef HAVE_APPLICATIVEDO
99
import AdoTests
1010
#endif
11+
import TestEquivDataSource
1112

1213
import Data.String
1314
import Test.HUnit
@@ -23,4 +24,5 @@ main = runTestTT $ TestList
2324
#ifdef HAVE_APPLICATIVEDO
2425
, TestLabel "AdoTests" AdoTests.tests
2526
#endif
27+
, TestLabel "EquivDataSource" TestEquivDataSource.tests
2628
]

tests/TestEquivDataSource.hs

+44
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,44 @@
1+
module TestEquivDataSource (tests) where
2+
3+
import Haxl.Prelude as Haxl
4+
import Prelude ()
5+
6+
import Haxl.Core
7+
8+
import EquivDataSource
9+
10+
import Data.IORef
11+
import Data.List (nub)
12+
import Test.HUnit
13+
14+
testEnv :: IO (Env ())
15+
testEnv = do
16+
myState <- EquivDataSource.initGlobalState
17+
let st = stateSet myState stateEmpty
18+
initEnv st ()
19+
20+
tests :: Test
21+
tests = TestList
22+
[ TestLabel "singleFetchTest" singleFetchTest
23+
, TestLabel "multiFetchTest" multiFetchTest
24+
]
25+
26+
singleFetchTest :: Test
27+
singleFetchTest = TestCase $ do
28+
env <- testEnv
29+
x <- runHaxl env $ mapM (getSimilar . MyData) [0, 7, 14, 21, 28]
30+
-- the numbers are all congruent modulo 7, so we expect one unique result for all of them
31+
assertEqual "unique result" 1 $ length (nub x)
32+
stats <- readIORef (statsRef env)
33+
-- ... and only one fetch
34+
assertEqual "fetches" 1 (numFetches stats)
35+
36+
multiFetchTest :: Test
37+
multiFetchTest = TestCase $ do
38+
env <- testEnv
39+
x <- runHaxl env $ mapM (getSimilar . MyData) [0 .. 13]
40+
-- expect seven unique results
41+
assertEqual "unique result" 7 $ length (nub x)
42+
stats <- readIORef (statsRef env)
43+
-- ... in seven fetches
44+
assertEqual "fetches" 7 (numFetches stats)

0 commit comments

Comments
 (0)