finite-1.4.1.2: Finite ranges via types
MaintainerFelix Klein
Safe HaskellNone
LanguageHaskell2010

Finite.TH

Description

Template haskell for easy instance generation using newtypes.

Synopsis

Documentation

newInstance :: String -> Q [Dec] Source #

Creates a new basic type using the name provided as a string. The template defines the corresponding data type using the provided name and a corresponding access function using the same name with the first letter moved to lower case. Furthermore, it also instanciates corresponding Show, Hashable, Ix, Arbitrary, and Num instances.

>>> newInstance "Example"

newtype Example =
  Example { example :: Int }
  deriving (Eq, Ord)

instance Show Example where
  show (Example x) = show x

instance Hashable Example where
  hashWithSalt s (Example x) = hashWithSalt s x

instance Ix Example where
  range (l,u) = map Example $ range (example l, example u)
  index (l,u) x = index (example l, example u) (example x)
  inRange (l,u) x = inRange (example l, example u) (example x)

instance Arbitrary Example where
  arbitrary = Example <$> arbitrary
  shrink (Example x) = map Example $ shrink x

instance Num Example where
  (Example x) + (Example y) = Example (a + b)
  (Example x) - (Example y) = Example (a - b)
  (Example x) * (Example y) = Example (a * b)
  abs = Example . abs . example
  negate = Example . negage . example
  signum = Example . signum . example
  fromInteger = Example . fromInteger

baseInstance :: Q Type -> Q Exp -> String -> Q [Dec] Source #

Creates a basic finite instance using the bounds provided via the first argument, the access function provided by the second argument and the name provided as a string.

>>> baseInstance [t|Bounds|] [|getBound|] "Example"

instance Finite Bounds Example where
  elements _ = getBound ?bounds
  value = Example
  index = example

extendInstance :: Q Type -> Q Type -> Q Exp -> Q [Dec] Source #

Extends a Finite instance to an extended parameter space. The first argument takes the type to be extended, the second argument the type of the new parameter space and the third argument a translator function that translates the old parameter space into the new one.

>>> :i Bounds

instance Finite Bounds Example

>>> :t derive

derive :: NewBounds -> Bounds

>>> extendInstance [t|Example|] [t|NewBounds] [|translate|]

instance Finite NewBounds Example where
  elements = let ?bounds = translate ?bounds in elements
  offset = let ?bounds = translate ?bounds in offset
  value = let ?bounds = translate ?bounds in value
  index = let ?bounds = translate ?bounds in index

polyType :: Q Type -> String -> Q Type Source #

Constructs a polymorph type given a type constructor and a free type variable. Such a construction cannot be expressed in quotation syntax directly.

>>> polyType [t|Maybe|] "a"

Maybe a