Safe Haskell | None |
---|---|
Language | Haskell2010 |
A tradgey has befallen us. Newtypes, something intended to be a zero-cost abstraction is having a cost. May the phantoms save us.
Synopsis
- data Spooky (s :: Type) (a :: Type)
- class s 👻 a where
- traumatize :: s -> Spooky s a
- terrify :: Spooky s a -> s
- mapSpooky :: (s 👻 a, s 👻 b) => (a -> b) -> Spooky s a -> Spooky s b
- applySpooky :: forall s a b. (s 👻 (a -> b), s 👻 a, s 👻 b) => Spooky s (a -> b) -> Spooky s a -> Spooky s b
- bindSpooky :: s 👻 a => Spooky s a -> (a -> Spooky s b) -> Spooky s b
- hoistSpooky :: (s -> s') -> Spooky s a -> Spooky s' a
- liftSpooky :: s 👻 a => (a -> b) -> Spooky s a -> b
- liftSpooky2 :: (s 👻 a, s 👻 b) => (a -> b -> c) -> Spooky s a -> Spooky s b -> c
- liftSpooky3 :: (s 👻 a, s 👻 b, s 👻 c) => (a -> b -> c -> d) -> Spooky s a -> Spooky s b -> Spooky s c -> d
- liftSpooky4 :: (s 👻 a, s 👻 b, s 👻 c, s 👻 d) => (a -> b -> c -> d -> e) -> Spooky s a -> Spooky s b -> Spooky s c -> Spooky s d -> e
- liftSpooky5 :: (s 👻 a, s 👻 b, s 👻 c, s 👻 d, s 👻 e) => (a -> b -> c -> d -> e -> f) -> Spooky s a -> Spooky s b -> Spooky s c -> Spooky s d -> Spooky s e -> f
Documentation
data Spooky (s :: Type) (a :: Type) Source #
Spooky is either a newtype over s
, or a type alias of s
depending on the cabal flag -untyped.
a
is always a phantom type. The haddock is somewhat misleading here, as it's compiled typed
and therefore reflects the newtyped representation below.
Instances
Bounded s => Bounded (Spooky s a) Source # | |
Enum s => Enum (Spooky s a) Source # | |
Defined in Data.Spooky succ :: Spooky s a -> Spooky s a # pred :: Spooky s a -> Spooky s a # fromEnum :: Spooky s a -> Int # enumFrom :: Spooky s a -> [Spooky s a] # enumFromThen :: Spooky s a -> Spooky s a -> [Spooky s a] # enumFromTo :: Spooky s a -> Spooky s a -> [Spooky s a] # enumFromThenTo :: Spooky s a -> Spooky s a -> Spooky s a -> [Spooky s a] # | |
Eq s => Eq (Spooky s a) Source # | |
Ord s => Ord (Spooky s a) Source # | |
Read s => Read (Spooky s a) Source # | |
Show s => Show (Spooky s a) Source # | |
Generic (Spooky s a) Source # | |
type Rep (Spooky s a) Source # | |
Defined in Data.Spooky |
Ghostly relation
The class of semantic types that can be converted to and from Spooky.
Typically these methods are defined in terms of terrify
and traumatize
Coercion
traumatize :: s -> Spooky s a Source #
Now s
masquerades around like it was converted from a
.
This function should be considered regrettable, and perhaps
only used in the definition of a 👻 instance. This function
breaks any guarentee that we had, that a
is semantic for s
.
Use with care.
Standard toolchain
mapSpooky :: (s 👻 a, s 👻 b) => (a -> b) -> Spooky s a -> Spooky s b Source #
Spooky is a Functor, but we cannot make a type class instance for it because type aliases cannot be curried in Haskell
applySpooky :: forall s a b. (s 👻 (a -> b), s 👻 a, s 👻 b) => Spooky s (a -> b) -> Spooky s a -> Spooky s b Source #
Applicative operation for Spooky
bindSpooky :: s 👻 a => Spooky s a -> (a -> Spooky s b) -> Spooky s b Source #
Monadic operation for Spooky
hoistSpooky :: (s -> s') -> Spooky s a -> Spooky s' a Source #
When the villian actually does change
Lift arguments
liftSpooky :: s 👻 a => (a -> b) -> Spooky s a -> b Source #
Lift the argument of a function into Spooky
liftSpooky3 :: (s 👻 a, s 👻 b, s 👻 c) => (a -> b -> c -> d) -> Spooky s a -> Spooky s b -> Spooky s c -> d Source #