spooky-0.1.0.0: Unified api for phantom typed newtypes and type aliases
Safe HaskellNone
LanguageHaskell2010

Data.Spooky

Description

A tradgey has befallen us. Newtypes, something intended to be a zero-cost abstraction is having a cost. May the phantoms save us.

Synopsis

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

Instances details
Bounded s => Bounded (Spooky s a) Source # 
Instance details

Defined in Data.Spooky

Methods

minBound :: Spooky s a

maxBound :: Spooky s a

Enum s => Enum (Spooky s a) Source # 
Instance details

Defined in Data.Spooky

Methods

succ :: Spooky s a -> Spooky s a

pred :: Spooky s a -> Spooky s a

toEnum :: Int -> 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 # 
Instance details

Defined in Data.Spooky

Methods

(==) :: Spooky s a -> Spooky s a -> Bool

(/=) :: Spooky s a -> Spooky s a -> Bool

Ord s => Ord (Spooky s a) Source # 
Instance details

Defined in Data.Spooky

Methods

compare :: Spooky s a -> Spooky s a -> Ordering

(<) :: Spooky s a -> Spooky s a -> Bool

(<=) :: Spooky s a -> Spooky s a -> Bool

(>) :: Spooky s a -> Spooky s a -> Bool

(>=) :: Spooky s a -> Spooky s a -> Bool

max :: Spooky s a -> Spooky s a -> Spooky s a

min :: Spooky s a -> Spooky s a -> Spooky s a

Read s => Read (Spooky s a) Source # 
Instance details

Defined in Data.Spooky

Methods

readsPrec :: Int -> ReadS (Spooky s a)

readList :: ReadS [Spooky s a]

readPrec :: ReadPrec (Spooky s a)

readListPrec :: ReadPrec [Spooky s a]

Show s => Show (Spooky s a) Source # 
Instance details

Defined in Data.Spooky

Methods

showsPrec :: Int -> Spooky s a -> ShowS

show :: Spooky s a -> String

showList :: [Spooky s a] -> ShowS

Generic (Spooky s a) Source # 
Instance details

Defined in Data.Spooky

Associated Types

type Rep (Spooky s a) :: Type -> Type

Methods

from :: Spooky s a -> Rep (Spooky s a) x

to :: Rep (Spooky s a) x -> Spooky s a

type Rep (Spooky s a) Source # 
Instance details

Defined in Data.Spooky

type Rep (Spooky s a) = D1 ('MetaData "Spooky" "Data.Spooky" "spooky-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Spooky" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s)))

Ghostly relation

class s 👻 a where Source #

The class of semantic types that can be converted to and from Spooky. Typically these methods are defined in terms of terrify and traumatize

Methods

unSpooky :: Spooky s a -> a Source #

Convert s to a

toSpooky :: a -> Spooky s a Source #

Convert a to s

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.

terrify :: Spooky s a -> s Source #

Scooby pulled the mask off and it was farmer s the whole time.

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

liftSpooky2 :: (s 👻 a, s 👻 b) => (a -> b -> c) -> Spooky s a -> Spooky s b -> c Source #

liftSpooky3 :: (s 👻 a, s 👻 b, s 👻 c) => (a -> b -> c -> d) -> Spooky s a -> Spooky s b -> Spooky s c -> d Source #

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 Source #

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 Source #