inferno-core-0.1.0.0: A statically-typed functional scripting language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Inferno.Module.Cast

Synopsis

Documentation

type Either3 a b c = Either a (Either b c) Source #

type Either4 a b c d = Either a (Either3 b c d) Source #

type Either5 a b c d e = Either a (Either4 b c d e) Source #

type Either6 a b c d e f = Either a (Either5 b c d e f) Source #

type Either7 a b c d e f g = Either a (Either6 b c d e f g) Source #

class ToValue c m a where Source #

Types that can be converted to script values, allowing IO in the process.

Methods

toValue :: MonadError EvalError m => a -> m (Value c m) Source #

Instances

Instances details
ToValue c m CTime Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: CTime -> m (Value c m) Source #

ToValue c m Int64 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Int64 -> m (Value c m) Source #

ToValue c m Word16 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Word16 -> m (Value c m) Source #

ToValue c m Word32 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Word32 -> m (Value c m) Source #

ToValue c m Word64 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Word64 -> m (Value c m) Source #

ToValue c m Lit Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Lit -> m (Value c m) Source #

ToValue c m Text Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Text -> m (Value c m) Source #

ToValue c m Integer Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Integer -> m (Value c m) Source #

ToValue c m () Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: () -> m (Value c m) Source #

ToValue c m Bool Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Bool -> m (Value c m) Source #

ToValue c m Double Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Double -> m (Value c m) Source #

ToValue c m Int Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Int -> m (Value c m) Source #

ToValue c m a => ToValue c m (Maybe a) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Maybe a -> m (Value c m) Source #

ToValue c m a => ToValue c m [a] Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: [a] -> m (Value c m) Source #

ToValue c m (m (Value c m)) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: m (Value c m) -> m (Value c m) Source #

(ToValue c m a, ToValue c m b) => ToValue c m (Either a b) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Either a b -> m (Value c m) Source #

ToValue c m (Value c m) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: Value c m -> m (Value c m) Source #

(FromValue c m a, ToValue c m b) => ToValue c m (a -> b) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: (a -> b) -> m (Value c m) Source #

(Monad m, FromValue c (ImplEnvM m c) a1, FromValue c (ImplEnvM m c) a2, ToValue c (ImplEnvM m c) a3, KnownSymbol lbl) => ToValue c (ImplEnvM m c) (ImplicitCast lbl a1 a2 a3) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toValue :: ImplicitCast lbl a1 a2 a3 -> ImplEnvM m c (Value c (ImplEnvM m c)) Source #

class FromValue c m a where Source #

Class of types that can be converted from script values.

Methods

fromValue :: MonadError EvalError m => Value c m -> m a Source #

Instances

Instances details
Pretty c => FromValue c m CTime Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m CTime Source #

Pretty c => FromValue c m Int64 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Int64 Source #

Pretty c => FromValue c m Word16 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Word16 Source #

Pretty c => FromValue c m Word32 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Word32 Source #

Pretty c => FromValue c m Word64 Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Word64 Source #

Pretty c => FromValue c m Text Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Text Source #

Pretty c => FromValue c m Integer Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Integer Source #

Pretty c => FromValue c m () Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m () Source #

Pretty c => FromValue c m Bool Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Bool Source #

Pretty c => FromValue c m Double Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Double Source #

Pretty c => FromValue c m Int Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m Int Source #

(Typeable a, FromValue c m a, Pretty c) => FromValue c m (Maybe a) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m (Maybe a) Source #

(Typeable a, FromValue c m a, Pretty c) => FromValue c m [a] Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m [a] Source #

(FromValue c m a, FromValue c m b) => FromValue c m (Either a b) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m (Either a b) Source #

FromValue c m (Value c m) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

fromValue :: Value c m -> m (Value c m) Source #

class Kind0 a where Source #

Haskell types that can be casted to mask script types.

Instances

Instances details
Kind0 CTime Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Int64 Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Word16 Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Word32 Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Word64 Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Text Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Integer Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 () Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toType :: Proxy () -> InfernoType Source #

Kind0 Bool Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Double Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Float Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 Int Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 a => Kind0 (IO a) Source #

In this instance, the IO in the type is ignored.

Instance details

Defined in Inferno.Module.Cast

Methods

toType :: Proxy (IO a) -> InfernoType Source #

Kind0 a => Kind0 (Maybe a) Source # 
Instance details

Defined in Inferno.Module.Cast

Kind0 a => Kind0 [a] Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toType :: Proxy [a] -> InfernoType Source #

Kind0 (Either a b) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toType :: Proxy (Either a b) -> InfernoType Source #

(Kind0 a, Kind0 b) => Kind0 (a -> b) Source # 
Instance details

Defined in Inferno.Module.Cast

Methods

toType :: Proxy (a -> b) -> InfernoType Source #

couldNotCast :: forall c m a. (Pretty c, MonadError EvalError m, Typeable a) => Value c m -> m a Source #