if-instance: Branch on whether a constraint is satisfied

[ bsd3, library, plugin, type-system ] [ Propose Tags ]
This version is deprecated.

This library provides a mechanism that can be used to branch on whether a constraint is satisfied (not limited to typeclass instances, despite the name of the library).

Usage example:

{-# OPTIONS_GHC -fplugin=IfSat.Plugin #-}

module MyModule where

import Data.Constraint.If ( IfSat(ifSat) )

hypot :: forall a. ( Floating a, IfSat (FMA a) ) => a -> a -> a
hypot = ifSat @(FMA a) withFMA withoutFMA
  where
    withFMA :: FMA a => a -> a -> a
    withFMA a b =
      let
        h = sqrt $ fma a a (b * b)
        h² = h * h
        a² = a * a
        x = fma (-b) b (h² - a²) + fma h h (-h²) - fma a a (-a²)
      in
        h - x / ( 2 * h )
    withoutFMA :: a -> a -> a
    withoutFMA a b = sqrt ( a * a + b * b )

Here we select between two ways of computing the hypotenuse function based on whether we have access to the fused multiply-add operation

 fma :: FMA a => a -> a -> a -> a

which computes \ a b c -> ( a * b ) + c in a single instruction, providing stronger guarantees about precision of the resul.

A call of the form hypot @MyNumberType will either use the robust withFMA function when an FMA MyNumberType instance is available, or will fallback to the simple withoutFMA implementation when no such instance can be found.

Modules

[Index] [Quick Jump]

  • Data
    • Constraint
      • Data.Constraint.If
  • IfSat
    • IfSat.Plugin

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.2.0.0, 0.2.1.0, 0.2.1.1, 0.3.0.0, 0.3.1.0, 0.4.0.0, 0.5.0.0, 0.5.1.0 (info)
Change log changelog.md
Dependencies base (>=4.14.0 && <4.18), ghc (>=9.0 && <9.6), ghc-tcplugin-api (>=0.5.1.0 && <0.6), if-instance [details]
License BSD-3-Clause
Copyright 2021 Sam Derbyshire
Author Sam Derbyshire
Maintainer Sam Derbyshire
Category Type System, Plugin
Home page https://github.com/sheaf/if-instance
Uploaded by sheaf at 2021-08-31T00:00:27Z
Distributions NixOS:0.5.1.0
Downloads 574 total (25 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]