IDynamic-0.1: Indexable, serializable form of Data.DynamicSource codeContentsIndex
Data.IDynamic
Synopsis
data IDynamic = forall a . (Typeable a, IResource a) => IDynamic a
list :: MVar (Map Word (IDynamic -> IO (Maybe IDynamic), String -> IDynamic))
class DynamicInterface x where
toIDyn :: x -> IDynamic
registerType :: IO x
fromIDyn :: IDynamic -> x
unsafeFromIDyn :: IDynamic -> x
safeFromIDyn :: IDynamic -> Maybe x
data Key = Key TypeRep String
Documentation
data IDynamic Source

Data.IDynamic is a indexable and serializable version Data.Dynamic . IDinamic provices methods for safe casting, serializaton, deserialization, registration output and input

the data definition of IDymanic is as such: data IDynamic= forall a. (Typeable a, IResource a) => IDynamic a deriving Typeable

The registration trough registerType is necessary before deserialization: registerType :: IO Type

example:

module Main where
import Data.IResource
import Data.IDynamic
import Data.Typeable

instance IResource Int where     
       keyResource x=  "I"
       serialize = show
       deserialize = read
       defPath _= "data/ "

instance IResource String where
       keyResource x=  take 5 x
       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

let list= [IDynamic x, IDynamic "hello, how are you"]

let assoc= zip (map keyResource list) list
      print $ lookup (keyResource (5 ::Int)) assoc

mapM writeResource list
      mds <-  readResource $  IDynamic  "hello"
      case mds of
            Nothing -> error "must have been Just!"
            Just ds -> do
                     putStrLn $ serialize ds
                     let str= fromIDyn  ds ::   String
                     putStrLn str

let y=  fromIDyn  ds ::   Int   -- casting error
                     print y
Constructors
forall a . (Typeable a, IResource a) => IDynamic a
show/hide Instances
list :: MVar (Map Word (IDynamic -> IO (Maybe IDynamic), String -> IDynamic))Source
class DynamicInterface x whereSource
DynamicInterface groups a set of default method calls to handle dynamic objects. It is not necessary to derive instances from it
Methods
toIDynSource
:: x
-> IDynamicencapsulates data in a dynamic object
registerTypeSource
:: IO xregisters the deserialize, readp and readResource methods for this data type
fromIDynSource
:: IDynamic
-> xextract the data from the dynamic object. trows a user error when the cast fails
unsafeFromIDynSource
:: IDynamic
-> xunsafe version.
safeFromIDynSource
:: IDynamic
-> Maybe xsafe extraction with Maybe
data Key Source

Key datatype can be used to read any object trough the Dynamic interface.

 data Key =  Key TypeRep String deriving Typeable

Example

  mst <- getDResource $ Key type keyofDesiredObject
             case mst of
               Nothing -> error $ "not found "++ key
               Just (idyn) ->  fromIDyn idyn :: DesiredDatatype}
Constructors
Key TypeRep String
show/hide Instances
Produced by Haddock version 2.4.2