home *** CD-ROM | disk | FTP | other *** search
/ PSION CD 2 / PsionCDVol2.iso / Programs / 876 / hugs.sis / Dynamic.lhs < prev    next >
Encoding:
Text File  |  2000-09-21  |  11.9 KB  |  477 lines

  1. %
  2. % (c) AQUA Project, Glasgow University, 1998
  3. %
  4.  
  5. Cheap and cheerful dynamic types.
  6.  
  7. The Dynamic interface is part of the Hugs/GHC standard
  8. libraries, providing basic support for dynamic types.
  9.  
  10. Operations for injecting values of arbitrary type into
  11. a dynamically typed value, Dynamic, are provided, together
  12. with operations for converting dynamic values into a concrete
  13. (monomorphic) type.
  14.  
  15. The Dynamic implementation provided is closely based on code
  16. contained in Hugs library of the same name.
  17.  
  18. NOTE: test code at the end, but commented out.
  19.  
  20. \begin{code}
  21. module Dynamic
  22.     (
  23.       -- dynamic type
  24.       Dynamic      -- abstract, instance of: Show (?)
  25.     , toDyn       -- :: Typeable a => a -> Dynamic
  26.     , fromDyn      -- :: Typeable a => Dynamic -> a -> a
  27.     , fromDynamic -- :: Typeable a => Dynamic -> Maybe a
  28.     
  29.       -- type representation
  30.  
  31.     , Typeable(typeOf) 
  32.       -- class Typeable a where { typeOf :: a -> TypeRep }
  33.  
  34.       -- Dynamic defines Typeable instances for the following
  35.       -- Prelude types: Char, Int, Float, Double, Bool
  36.       --                (), Maybe a, (a->b), [a]
  37.       --        (a,b) (a,b,c) (a,b,c,d) (a,b,c,d,e)
  38.  
  39.     , TypeRep      -- abstract, instance of: Eq, Show
  40.     , TyCon        -- abstract, instance of: Eq, Show
  41.  
  42.       -- type representation constructors/operators:
  43.     , mkTyCon       -- :: String  -> TyCon
  44.     , mkAppTy       -- :: TyCon   -> [TypeRep] -> TypeRep
  45.     , mkFunTy      -- :: TypeRep -> TypeRep   -> TypeRep
  46.     , applyTy       -- :: TypeRep -> TypeRep   -> Maybe TypeRep
  47.  
  48.       -- 
  49.       -- let iTy = mkTyCon "Int" in show (mkAppTy (mkTyCon ",,")
  50.       --                                 [iTy,iTy,iTy])
  51.       -- 
  52.       -- returns "(Int,Int,Int)"
  53.       --
  54.       -- The TypeRep Show instance promises to print tuple types
  55.       -- correctly. Tuple type constructors are specified by a 
  56.       -- sequence of commas, e.g., (mkTyCon ",,,,,,") returns
  57.       -- the 7-tuple tycon.
  58.     ) where
  59.  
  60. {- BEGIN_FOR_GHC
  61. import GlaExts
  62. import PrelDynamic
  63.    END_FOR_GHC -}
  64.  
  65. import IOExts 
  66.        ( unsafePerformIO,
  67.          IORef, newIORef, readIORef, writeIORef
  68.         )
  69.  
  70. {- BEGIN_FOR_HUGS -}
  71. data TypeRep
  72.  = App TyCon   [TypeRep]
  73.  | Fun TypeRep TypeRep
  74.    deriving ( Eq )
  75.  
  76. -- type constructors are 
  77. data TyCon = TyCon Int String
  78.  
  79. instance Eq TyCon where
  80.   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
  81.  
  82. data Dynamic = Dynamic TypeRep Obj
  83.  
  84. data Obj = Obj  
  85.  -- dummy type to hold the dynamically typed value.
  86.  
  87. primitive unsafeCoerce "primUnsafeCoerce" :: a -> b
  88. {- END_FOR_HUGS -}
  89.  
  90. {- BEGIN_FOR_GHC
  91. unsafeCoerce :: a -> b
  92. unsafeCoerce = unsafeCoerce#
  93.    END_FOR_GHC -}
  94. \end{code}
  95.  
  96. The dynamic type is represented by Dynamic, carrying
  97. the dynamic value along with its type representation:
  98.  
  99. \begin{code}
  100. -- the instance just prints the type representation.
  101. instance Show Dynamic where
  102.    showsPrec _ (Dynamic t _) = 
  103.           showString "<<" . 
  104.       showsPrec 0 t   . 
  105.       showString ">>"
  106. \end{code}
  107.  
  108. Operations for going to and from Dynamic:
  109.  
  110. \begin{code}
  111. toDyn :: Typeable a => a -> Dynamic
  112. toDyn v = Dynamic (typeOf v) (unsafeCoerce v)
  113.  
  114. fromDyn :: Typeable a => Dynamic -> a -> a
  115. fromDyn (Dynamic t v) def
  116.   | typeOf def == t = unsafeCoerce v
  117.   | otherwise       = def
  118.  
  119. fromDynamic :: Typeable a => Dynamic -> Maybe a
  120. fromDynamic (Dynamic t v) =
  121.   case unsafeCoerce v of 
  122.     r | t == typeOf r -> Just r
  123.       | otherwise     -> Nothing
  124. \end{code}
  125.  
  126. (Abstract) universal datatype:
  127.  
  128. \begin{code}
  129. instance Show TypeRep where
  130.   showsPrec p (App tycon tys) =
  131.     case tys of
  132.       [] -> showsPrec p tycon
  133.       [x] | tycon == listTc    -> showChar '[' . shows x . showChar ']'
  134.       xs  
  135.         | isTupleTyCon tycon -> showTuple tycon xs
  136.     | otherwise         ->
  137.         showParen (p > 9) $
  138.            showsPrec p tycon . 
  139.         showChar ' '      . 
  140.         showArgs tys
  141.  
  142.   showsPrec p (Fun f a) =
  143.      showParen (p > 8) $
  144.      showsPrec 9 f . showString " -> " . showsPrec 8 a
  145. \end{code}
  146.  
  147. To make it possible to convert values with user-defined types
  148. into type Dynamic, we need a systematic way of getting
  149. the type representation of an arbitrary type. Type class
  150. provide a good fit, here
  151.  
  152. \begin{code}
  153. class Typeable a where
  154.   typeOf :: a -> TypeRep
  155. \end{code}
  156.  
  157. NOTE: The argument to the overloaded `typeOf' is only
  158. used to carry type information, and Typeable instances
  159. should *never* look at its value.
  160.  
  161. \begin{code}
  162. isTupleTyCon :: TyCon -> Bool
  163. isTupleTyCon (TyCon _ (',':_)) = True
  164. isTupleTyCon _               = False
  165.  
  166. instance Show TyCon where
  167.   showsPrec _ (TyCon _ s) = showString s
  168.  
  169. -- 
  170. -- If we enforce the restriction that TyCons are
  171. -- shared, we can map them onto Ints very simply
  172. -- which allows for efficient comparison.
  173. --
  174. mkTyCon :: String -> TyCon
  175. mkTyCon str = unsafePerformIO $ do
  176.    v <- readIORef uni
  177.    writeIORef uni (v+1)
  178.    return (TyCon v str)
  179.  
  180. uni :: IORef Int
  181. uni = unsafePerformIO ( newIORef 0 )
  182. \end{code}
  183.  
  184. Some (Show.TypeRep) helpers:
  185.  
  186. \begin{code}
  187. showArgs :: Show a => [a] -> ShowS
  188. showArgs [] = id
  189. showArgs [a] = showsPrec 10 a
  190. showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
  191.  
  192. showTuple :: TyCon -> [TypeRep] -> ShowS
  193. showTuple (TyCon _ str) args = showChar '(' . go str args
  194.  where
  195.   go [] [a] = showsPrec 10 a . showChar ')'
  196.   go _  []  = showChar ')' -- a failure condition, really.
  197.   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
  198.   go _ _   = showChar ')'
  199. \end{code}
  200.  
  201. \begin{code}
  202. mkAppTy  :: TyCon   -> [TypeRep] -> TypeRep
  203. mkAppTy tyc args = App tyc args
  204.  
  205. mkFunTy  :: TypeRep -> TypeRep   -> TypeRep
  206. mkFunTy f a = Fun f a
  207. \end{code}
  208.  
  209. Auxillary functions
  210.  
  211. \begin{code}
  212. -- (f::(a->b)) `dynApply` (x::a) = (f a)::b
  213. dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
  214. dynApply (Dynamic t1 f) (Dynamic t2 x) =
  215.   case applyTy t1 t2 of
  216.     Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
  217.     Nothing -> Nothing
  218.  
  219. dynApp :: Dynamic -> Dynamic -> Dynamic
  220. dynApp f x = case dynApply f x of 
  221.              Just r -> r
  222.              Nothing -> error ("Type error in dynamic application.\n" ++
  223.                                "Can't apply function " ++ show f ++
  224.                                " to argument " ++ show x)
  225.  
  226. applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
  227. applyTy (Fun t1 t2) t3
  228.   | t1 == t3    = Just t2
  229. applyTy _ _     = Nothing
  230.  
  231. \end{code}
  232.  
  233. \begin{code}
  234. instance Typeable Int where
  235.   typeOf _ = mkAppTy intTc []
  236.   
  237. instance Typeable Char where
  238.   typeOf _ = mkAppTy charTc []
  239.   
  240. instance Typeable Bool where
  241.   typeOf _ = mkAppTy boolTc []
  242.   
  243. instance Typeable Float where
  244.   typeOf _ = mkAppTy floatTc []
  245.   
  246. instance Typeable Double where
  247.   typeOf _ = mkAppTy doubleTc []
  248.  
  249. instance Typeable Integer where
  250.   typeOf _ = mkAppTy integerTc []
  251.  
  252. instance Typeable a => Typeable (IO a) where
  253.   typeOf action = mkAppTy ioTc [typeOf (doIO action)]
  254.     where
  255.       doIO :: IO a -> a
  256.       doIO = undefined
  257.  
  258. instance Typeable a => Typeable [a] where
  259.   typeOf ls = mkAppTy listTc [typeOf (hd ls)]
  260.     where
  261.       hd :: [a] -> a
  262.       hd = undefined
  263.  
  264. instance Typeable a => Typeable (Maybe a) where
  265.   typeOf mb = mkAppTy maybeTc [typeOf (getJ mb)]
  266.     where
  267.       getJ :: Maybe a -> a
  268.       getJ = undefined
  269.  
  270. instance (Typeable a, Typeable b) => Typeable (Either a b) where
  271.   typeOf ei = mkAppTy maybeTc [typeOf (getL ei), typeOf (getR ei)]
  272.     where
  273.       getL :: Either a b -> a
  274.       getL = undefined
  275.       getR :: Either a b -> a
  276.       getR = undefined
  277.  
  278. instance (Typeable a, Typeable b) => Typeable (a -> b) where
  279.   typeOf f = mkFunTy (typeOf (arg f)) (typeOf (res f))
  280.    where
  281.     arg :: (a -> b) -> a
  282.     arg = undefined
  283.     
  284.     res :: (a -> b) -> b
  285.     res = undefined
  286.  
  287. instance Typeable () where
  288.   typeOf _ = mkAppTy unitTc []
  289.  
  290. instance Typeable TypeRep where
  291.   typeOf _ = mkAppTy typeRepTc []
  292.  
  293. instance Typeable TyCon where
  294.   typeOf _ = mkAppTy tyConTc []
  295.  
  296. instance Typeable Dynamic where
  297.   typeOf _ = mkAppTy dynamicTc []
  298.  
  299. instance Typeable Ordering where
  300.   typeOf _ = mkAppTy orderingTc []
  301.  
  302. instance (Typeable a, Typeable b) => Typeable (a,b) where
  303.   typeOf tu = mkAppTy tup2Tc [typeOf (fst tu), typeOf (snd tu)]
  304.     where
  305.       fst :: (a,b) -> a
  306.       fst = undefined
  307.       snd :: (a,b) -> b
  308.       snd = undefined
  309.  
  310.       tup2Tc = mkTyCon ","
  311.  
  312. instance ( Typeable a
  313.          , Typeable b
  314.      , Typeable c) => Typeable (a,b,c) where
  315.   typeOf tu = mkAppTy tup3Tc [ typeOf (fst tu)
  316.                              , typeOf (snd tu)
  317.                  , typeOf (thd tu)
  318.                  ]
  319.     where
  320.       fst :: (a,b,c) -> a
  321.       fst = undefined
  322.       snd :: (a,b,c) -> b
  323.       snd = undefined
  324.       thd :: (a,b,c) -> c
  325.       thd = undefined
  326.  
  327.       tup3Tc = mkTyCon ",,"
  328.  
  329. instance ( Typeable a
  330.      , Typeable b
  331.      , Typeable c
  332.      , Typeable d) => Typeable (a,b,c,d) where
  333.   typeOf tu = mkAppTy tup4Tc [ typeOf (fst tu)
  334.                              , typeOf (snd tu)
  335.                  , typeOf (thd tu)
  336.                  , typeOf (fth tu)
  337.                  ]
  338.     where
  339.       fst :: (a,b,c,d) -> a
  340.       fst = undefined
  341.       snd :: (a,b,c,d) -> b
  342.       snd = undefined
  343.       thd :: (a,b,c,d) -> c
  344.       thd = undefined
  345.       fth :: (a,b,c,d) -> d
  346.       fth = undefined
  347.  
  348.       tup4Tc = mkTyCon ",,,"
  349.  
  350. instance ( Typeable a
  351.      , Typeable b
  352.      , Typeable c
  353.      , Typeable d
  354.      , Typeable e) => Typeable (a,b,c,d,e) where
  355.   typeOf tu = mkAppTy tup5Tc [ typeOf (fst tu)
  356.                              , typeOf (snd tu)
  357.                  , typeOf (thd tu)
  358.                  , typeOf (fth tu)
  359.                  , typeOf (ffth tu)
  360.                  ]
  361.     where
  362.       fst :: (a,b,c,d,e) -> a
  363.       fst = undefined
  364.       snd :: (a,b,c,d,e) -> b
  365.       snd = undefined
  366.       thd :: (a,b,c,d,e) -> c
  367.       thd = undefined
  368.       fth :: (a,b,c,d,e) -> d
  369.       fth = undefined
  370.       ffth :: (a,b,c,d,e) -> e
  371.       ffth = undefined
  372.  
  373.       tup5Tc = mkTyCon ",,,,"
  374.  
  375. \end{code}
  376.  
  377. @TyCon@s are provided for the following:
  378.  
  379. \begin{code}
  380. -- prelude types:
  381. intTc, charTc, boolTc :: TyCon
  382. intTc      = mkTyCon "Int"
  383. charTc     = mkTyCon "Char"
  384. boolTc     = mkTyCon "Bool"
  385.  
  386. floatTc, doubleTc, integerTc :: TyCon
  387. floatTc    = mkTyCon "Float"
  388. doubleTc   = mkTyCon "Double"
  389. integerTc  = mkTyCon "Integer"
  390.  
  391. ioTc, maybeTc, eitherTc, listTc :: TyCon
  392. ioTc       = mkTyCon "IO"
  393. maybeTc    = mkTyCon "Maybe"
  394. eitherTc   = mkTyCon "Either"
  395. listTc     = mkTyCon "[]"
  396.  
  397. unitTc, orderingTc, arrayTc, complexTc, handleTc :: TyCon
  398. unitTc     = mkTyCon "()"
  399. orderingTc = mkTyCon "Ordering"
  400. arrayTc    = mkTyCon "Array"
  401. complexTc  = mkTyCon "Complex"
  402. handleTc   = mkTyCon "Handle"
  403.  
  404. -- Hugs/GHC extension lib types:
  405. addrTc, stablePtrTc, mvarTc :: TyCon
  406. addrTc       = mkTyCon "Addr"
  407. stablePtrTc  = mkTyCon "StablePtr"
  408. mvarTc       = mkTyCon "MVar"
  409.  
  410. foreignObjTc, stTc :: TyCon
  411. foreignObjTc = mkTyCon "ForeignObj"
  412. stTc         = mkTyCon "ST"
  413.  
  414. int8Tc, int16Tc, int32Tc, int64Tc :: TyCon
  415. int8Tc       = mkTyCon "Int8"
  416. int16Tc      = mkTyCon "Int16"
  417. int32Tc      = mkTyCon "Int32"
  418. int64Tc         = mkTyCon "Int64"
  419.  
  420. word8Tc, word16Tc, word32Tc, word64Tc :: TyCon
  421. word8Tc      = mkTyCon "Word8"
  422. word16Tc     = mkTyCon "Word16"
  423. word32Tc     = mkTyCon "Word32"
  424. word64Tc     = mkTyCon "Word64"
  425.  
  426. tyConTc, typeRepTc, dynamicTc :: TyCon
  427. tyConTc      = mkTyCon "TyCon"
  428. typeRepTc    = mkTyCon "Type"
  429. dynamicTc    = mkTyCon "Dynamic"
  430.  
  431. -- GHC specific:
  432. {- BEGIN_FOR_GHC
  433. byteArrayTc, mutablebyteArrayTc, wordTc :: TyCon
  434. byteArrayTc  = mkTyCon "ByteArray"
  435. mutablebyteArrayTc = mkTyCon "MutableByteArray"
  436. wordTc       = mkTyCon "Word"
  437.    END_FOR_GHC -}
  438.  
  439. \end{code}
  440.  
  441. begin{code}
  442. test1,test2, test3, test4 :: Dynamic
  443.  
  444. test1 = toDyn (1::Int)
  445. test2 = toDyn ((+) :: Int -> Int -> Int)
  446. test3 = dynApp test2 test1
  447. test4 = dynApp test3 test1
  448.  
  449. test5, test6,test7 :: Int
  450. test5 = fromDyn test4 0
  451. test6 = fromDyn test1 0
  452. test7 = fromDyn test2 0
  453.  
  454. test8 :: Dynamic
  455. test8 = toDyn (mkAppTy listTc)
  456.  
  457. test9 :: Float
  458. test9 = fromDyn test8 0
  459.  
  460. printf :: String -> [Dynamic] -> IO ()
  461. printf str args = putStr (decode str args)
  462.  where
  463.   decode [] [] = []
  464.   decode ('%':'n':cs) (d:ds) =
  465.     (\ v -> show v++decode cs ds) (fromDyn  d (0::Int))
  466.   decode ('%':'c':cs) (d:ds) =
  467.     (\ v -> show v++decode cs ds) (fromDyn  d ('\0'))
  468.   decode ('%':'b':cs) (d:ds) =
  469.     (\ v -> show v++decode cs ds) (fromDyn  d (False::Bool))
  470.   decode (x:xs) ds = x:decode xs ds
  471.  
  472. test10 :: IO ()
  473. test10 = printf "%n = %c, that much is %b\n" [toDyn (3::Int),toDyn 'a', toDyn False]
  474. end{code}
  475.  
  476.  
  477.