1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151
|
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Dynamic
-- Copyright : (c) The University of Glasgow 2001
-- License : BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer : libraries@haskell.org
-- Stability : experimental
-- Portability : portable
--
-- The Dynamic interface provides basic support for dynamic types.
--
-- Operations for injecting values of arbitrary type into
-- a dynamically typed value, Dynamic, are provided, together
-- with operations for converting dynamic values into a concrete
-- (monomorphic) type.
--
-----------------------------------------------------------------------------
module Data.Dynamic
(
-- * The @Dynamic@ type
Dynamic(..),
-- * Converting to and from @Dynamic@
toDyn,
fromDyn,
fromDynamic,
-- * Applying functions of dynamic type
dynApply,
dynApp,
dynTypeRep,
-- * Convenience re-exports
Typeable
) where
import Data.Type.Equality
import Type.Reflection
import Data.Maybe
import GHC.Base
import GHC.Show
import GHC.Exception
-------------------------------------------------------------
--
-- The type Dynamic
--
-------------------------------------------------------------
{-|
A value of type 'Dynamic' is an object encapsulated together with its type.
A 'Dynamic' may only represent a monomorphic value; an attempt to
create a value of type 'Dynamic' from a polymorphically-typed
expression will result in an ambiguity error (see 'toDyn').
'Show'ing a value of type 'Dynamic' returns a pretty-printed representation
of the object\'s type; useful for debugging.
-}
data Dynamic where
Dynamic :: forall a. TypeRep a -> a -> Dynamic
-- | @since 2.01
instance Show Dynamic where
-- the instance just prints the type representation.
showsPrec _ (Dynamic t _) =
showString "<<" .
showsPrec 0 t .
showString ">>"
-- here so that it isn't an orphan:
-- | @since 4.0.0.0
instance Exception Dynamic
-- Use GHC's primitive 'Any' type to hold the dynamically typed value.
--
-- In GHC's new eval/apply execution model this type must not look
-- like a data type. If it did, GHC would use the constructor convention
-- when evaluating it, and this will go wrong if the object is really a
-- function. Using Any forces GHC to use
-- a fallback convention for evaluating it that works for all types.
-- | Converts an arbitrary value into an object of type 'Dynamic'.
--
-- The type of the object must be an instance of 'Typeable', which
-- ensures that only monomorphically-typed objects may be converted to
-- 'Dynamic'. To convert a polymorphic object into 'Dynamic', give it
-- a monomorphic type signature. For example:
--
-- > toDyn (id :: Int -> Int)
--
toDyn :: Typeable a => a -> Dynamic
toDyn v = Dynamic typeRep v
-- | Converts a 'Dynamic' object back into an ordinary Haskell value of
-- the correct type. See also 'fromDynamic'.
fromDyn :: Typeable a
=> Dynamic -- ^ the dynamically-typed object
-> a -- ^ a default value
-> a -- ^ returns: the value of the first argument, if
-- it has the correct type, otherwise the value of
-- the second argument.
fromDyn (Dynamic t v) def
| Just HRefl <- t `eqTypeRep` typeOf def = v
| otherwise = def
-- | Converts a 'Dynamic' object back into an ordinary Haskell value of
-- the correct type. See also 'fromDyn'.
fromDynamic
:: forall a. Typeable a
=> Dynamic -- ^ the dynamically-typed object
-> Maybe a -- ^ returns: @'Just' a@, if the dynamically-typed
-- object has the correct type (and @a@ is its value),
-- or 'Nothing' otherwise.
fromDynamic (Dynamic t v)
| Just HRefl <- t `eqTypeRep` rep = Just v
| otherwise = Nothing
where rep = typeRep :: TypeRep a
-- (f::(a->b)) `dynApply` (x::a) = (f a)::b
dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
dynApply (Dynamic (Fun ta tr) f) (Dynamic ta' x)
| Just HRefl <- ta `eqTypeRep` ta'
, Just HRefl <- typeRep @Type `eqTypeRep` typeRepKind tr
= Just (Dynamic tr (f x))
dynApply _ _
= Nothing
dynApp :: Dynamic -> Dynamic -> Dynamic
dynApp f x = case dynApply f x of
Just r -> r
Nothing -> errorWithoutStackTrace ("Type error in dynamic application.\n" ++
"Can't apply function " ++ show f ++
" to argument " ++ show x)
dynTypeRep :: Dynamic -> SomeTypeRep
dynTypeRep (Dynamic tr _) = SomeTypeRep tr
|