{-# OPTIONS -XTypeSynonymInstances #-} -- XTypeSynonymInstances added only to permit IResource instances for Strings module Main where import Data.TCache.Dynamic import Data.Typeable import Unsafe.Coerce {------------- tests--------- example of IDynamic usage. -} --very simple data: --two objects with two different datatypes: Int and String instance IResource Int where keyResource x= "I" serialize = show deserialize = read defPath _= "data/" instance IResource String where keyResource x= "S" serialize = show deserialize = read defPath _= "data/" main= do putStrLn "see the code to know the meaning of he results" registerType :: IO Int -- register both datatypes (Int, and String) registerType :: IO String let x= 1:: Int withDResources [] (\_->[toIDyn x, toIDyn "hola"]) --resource creation for the example syncCache --syncCache now has no parameters (refcache is not used) res <- getResources [1::Int, 1::Int] --getResources works as allways print (res :: [Maybe Int]) res <- getResources ["hola", "hola"] --with multiple stored datatypes this time print (res :: [Maybe String]) res <- getDResources [toIDyn "hola", toIDyn ( 1::Int)] -- DResource calls can manage many datatypes simultaneously print res mres <- getResource $ Key (typeOf "") "S" --Key permits to retrieve any object of any datatype by key case mres of Nothing -> error "not found" Just res -> do print ( res :: String) -- print the content -- print ( res :: Int) -- error reported, wrong casting mres <- getDResource $ IDynamic $ Key (typeOf "") "S" --Key permits to retrieve any object of any datatype by key case mres of Nothing -> error "not found" Just res -> do print (fromIDyn res :: String) -- print the content print (fromIDyn res :: Int) -- error reported, wrong casting syncCache getChar