constraints-emerge: Defer instance lookups until runtime

[ constraints, library, mit ] [ Propose Tags ]

This plugin allows you to write

{-# OPTIONS_GHC -fplugin Data.Constraint.Emerge.Plugin #-}
module Test where

import Data.Constraint.Emerge

showAnything :: forall c. Emerge (Show c) => c -> String
showAnything c =
case emerge @(Show c) of
Just Dict -> show c
Nothing   -> "{{unshowable}}"

where the 'Emerge (Show c)' will automatically be discharged for any monomorphic c.

See test/EmergeSpec.hs for a few examples of what this plugin can do for you.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1, 0.1.1, 0.1.2 (info)
Change log ChangeLog.md
Dependencies base (>=4.9 && <5), constraints, containers, ghc (>=8.0.1), hashable [details]
License MIT
Copyright 2018 Sandy Maguire
Author Sandy Maguire
Maintainer sandy@sandymaguire.me
Category Constraints
Home page https://github.com/isovector/constraints-emerge
Source repo head: git clone git://github.com/isovector/constraints-emerge.git
Uploaded by isovector at 2018-04-19T13:14:45Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 1419 total (12 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-04-19 [all 1 reports]

Readme for constraints-emerge-0.1.2

[back to package description]

constraints-emerge: defer instance lookups until runtime

Build Status | Hackage

Dedication

Failure should be our teacher, not our undertaker. Failure is delay, not defeat. It is a temporary detour, not a dead end. Failure is something we can avoid only by saying nothing, doing nothing, and being nothing.

Denis Waitley

Synopsis

{-# LANGUAGE ConstraintKinds     #-}
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications    #-}
{-# OPTIONS_GHC -fplugin=Data.Constraint.Emerge.Plugin #-}

module Test where

import Data.Constraint.Emerge

showAnything :: forall c. Emerge (Show c) => c -> String
showAnything c =
  case emerge @(Show c) of
    Just Dict -> show c
    Nothing -> "<<unshowable>>"


showBool = showAnything True  -- "True"
showId   = showAnything id    -- "<<unshowable>>"

Known Bugs

  • constraints-emerge will generate type-equality dictionaries any types (even ones that aren't equal 😱 😱 😱)
  • It fails to provide Emerge c dictionaries at runtime.
  • The generated error messages mention mangled type variables; it would be cool if they didn't.

If someone wants to pick it up from here, that’d be great!

Contact

Please reports bugs and missing features at the GitHub bugtracker. This is also where you can find the source code.

constraints-emerge was written by Sandy Maguire and is licensed under a permissive MIT license.