Giter Site home page Giter Site logo

obsidiansystems / constraints-extras Goto Github PK

View Code? Open in Web Editor NEW
9.0 24.0 12.0 134 KB

Convenience functions and template haskell for working with constraints

Home Page: http://hackage.haskell.org/package/constraints-extras

License: Other

Haskell 79.40% Nix 20.60%
haskell constraints

constraints-extras's Introduction

constraints-extras

Example usage:

> {-# LANGUAGE GADTs #-}
> {-# LANGUAGE KindSignatures #-}
> {-# LANGUAGE PolyKinds #-}
> {-# LANGUAGE ScopedTypeVariables #-}
> {-# LANGUAGE TemplateHaskell #-}
> {-# LANGUAGE TypeApplications  #-}
> {-# LANGUAGE TypeFamilies #-}
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE ConstraintKinds #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE UndecidableInstances #-}
> {-# LANGUAGE ExistentialQuantification #-}
> {-# LANGUAGE TypeFamilies #-}
>
> import Data.Aeson
> import Data.Constraint.Forall
> import Data.Constraint.Extras
> import Data.Constraint.Extras.TH
>
> data A :: * -> * where
>   A_a :: A Int
>   A_b :: Int -> A ()
>
> deriveArgDict ''A
>
> data B :: * -> * where
>   B_a :: A a -> A a -> B a
>   B_x :: Int -> B Int
>
> deriveArgDict ''B
>
> data V :: (* -> *) -> * where
>   V_a :: A Int -> V A
>
> deriveArgDict ''V
>
> data family Fam a :: * -> *
> data instance Fam () :: * -> * where
>   FI :: Fam () Int
>   FB :: Fam () Bool
>
> deriveArgDict 'FI
> -- this derives an instance Has c (Fam ()) by looking up the associated data instance.
>
> data DSum k f = forall a. DSum (k a) (f a)
>
> -- Derive a ToJSON instance for our 'DSum'
> instance forall k f.
>   ( Has' ToJSON k f -- Given a value of type (k a), we can obtain an instance (ToJSON (f a))
>   , ForallF ToJSON k -- For any (a), we have an instance (ToJSON (k a))
>   ) => ToJSON (DSum k f) where
>   toJSON (DSum (k :: k a) f) = toJSON
>     ( whichever @ToJSON @k @a $ toJSON k -- Use the (ForallF ToJSON k) constraint to obtain the (ToJSON (k a)) instance
>     , has' @ToJSON @f k $ toJSON f -- Use the (Has' ToJSON k f) constraint to obtain the (ToJSON (f a)) instance
>     )
>
> data Some k = forall a. Some (k a)
>
> -- Derive a FromJSON instance for our 'DSum'
> instance (FromJSON (Some f), Has' FromJSON f g) => FromJSON (DSum f g) where
>   parseJSON x = do
>     (jf, jg) <- parseJSON x
>     Some (f :: f a) <- parseJSON jf
>     g <- has' @FromJSON @g f (parseJSON jg)
>     return $ DSum f g
>
> main :: IO ()
> main = return ()

constraints-extras's People

Contributors

3noch avatar alaendle avatar alexfmpe avatar ali-abrar avatar awjchen avatar cgibbard avatar danbornside avatar endgame avatar ericson2314 avatar felixonmars avatar int-e avatar jhrcek avatar jonathanlking avatar luigy avatar mitchellwrosen avatar mstksg avatar ryantrinkle avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

constraints-extras's Issues

Turn `readme` into a `test-suite`

So its dependencies aren't considered when constraints-extras is used a dependency by cabal-install.

(Also it would hide aeson from dependency list on Hackage)

Confusing deriveArgDict behaviour/error messages

Consider the following toy example:

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
module Example where

import Data.Constraint.Extras.TH (deriveArgDict)

data A a where
  MkA :: B a -> A a

data B a where
  MkB :: B ()

deriveArgDict ''A
deriveArgDict ''B

Compiling this errors with:

    • Could not deduce: c a
        arising from a use of ‘Data.Constraint.Dict’
      from the context: Data.Constraint.Extras.ConstraintsFor A c
        bound by the type signature for:
                   Data.Constraint.Extras.argDict :: forall a.
                                                     Data.Constraint.Extras.ConstraintsFor A c =>
                                                     A a -> Data.Constraint.Dict (c a)
    • In the expression: Data.Constraint.Dict
      In a case alternative: MkA {} -> Data.Constraint.Dict
      In the expression: \case MkA {} -> Data.Constraint.Dict
    • Relevant bindings include
        argDict :: A a -> Data.Constraint.Dict (c a)
   |
   | deriveArgDict ''A
   | ^^^^^^^^^^^^^^^^^

Dumping the splices (with -ddump-splices) we can see the generated code is:

instance Data.Constraint.Extras.ArgDict c A where
  type Data.Constraint.Extras.ConstraintsFor A c = ()
  Data.Constraint.Extras.argDict
    = \case MkA {} -> Data.Constraint.Dict

When instead I would expect it to generate:

instance Data.Constraint.Extras.ArgDict c A where
  type Data.Constraint.Extras.ConstraintsFor A c = (Data.Constraint.Extras.ConstraintsFor B c)
  Data.Constraint.Extras.argDict
    = \case MkA x -> Data.Constraint.Extras.argDict x

As the ArgDict instance for B has not been generated yet, hasArgDictInstance is False in deriveArgDict, so no ConstraintsFor B c/recursive call to argDict is generated.

A solution to this is to make sure deriveArgDict ''B comes before deriveArgDict ''A, which does generate the expected code, but this can be difficult to work out just from the error message.

I am curious what the hasArgDictInstance check actually prevents? Can we remove it, always "optimistically" generate constraints and just let GHC's constraint solver handle this for us (failing if the constraint can't be satisfied).

I have patched our copy of constraints-extras in our codebase to do this and haven't noticed any errors, but am very possibly missing something!

Poly-kinded indexes

It looks like #35 is pertinent, but I wonder if it's possible to write ArgDict instances with a particular case of poly kinded indicies:

{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DerivingStrategies #-}

module Foo where

import Data.Constraint.Extras.TH (deriveArgDict)
import Data.Aeson.GADT.TH (deriveJSONGADT)

data Foo = Foo | Bar 
    deriving stock (Generic)
    deriving anyclass (ToJSON, FromJSON)

data SFoo :: Foo -> * where 
    SFoo :: SFoo 'Foo
    SBar :: SFoo 'Bar

deriveArgDict ''SFoo

deriveJSONGADT ''SFoo

newtype Wrapped foo = Wrapped Int
data Baz (a :: k) where 
    BazFoo :: Int -> Baz 'Foo 
    BazBar :: Baz 'Bar
    BazSFoo :: SFoo foo -> Baz foo
    BazWrapped :: SFoo foo -> Baz (Wrapped foo)


deriveArgDict ''Baz

deriveJSONGADT ''Baz

The splice generated for the above is:

instance ArgDict c_a4GzC Baz where
  type ConstraintsFor Baz c_a4GzC = (c_a4GzC  'Foo, c_a4GzC  'Bar,
                                     ConstraintsFor SFoo c_a4GzC)
  argDict
    = \case
        BazFoo {} -> Dict
        BazBar {} -> Dict
        BazSFoo x_a4GzK -> argDict x_a4GzK

which fails because c_a4GRl is not polykinded.

Dropping the kind signature and removing the wrapped case works:

data Baz a where 
   BazFoo :: Int -> Baz 'Foo 
   BazBar :: Baz 'Bar
   BazSFoo :: SFoo foo -> Baz foo
   -- BazWrapped :: SFoo foo -> Baz (Wrapped foo)

but is not what I want.

TH error in deriveArgDict

Here https://github.com/reflex-frp/reflex-gadt-api/blob/develop/Readme.md
If I change the definition of CatApi from

> data CatApi a where
>   CatApi_Identify :: Text -> CatApi (Either Text Token)
>   CatApi_DogApi :: Token -> DogApi a -> CatApi a

to

> data CatApi a where
>   CatApi_Identify :: Text -> CatApi (Either Text Token)
>   CatApi_DogApi :: Token -> DogApi a -> CatApi (Either Text a)

I get this error

Readme.lhs:99:3: error:
    The exact Name ‘a_Xhvt’ is not in scope
      Probable cause: you used a unique Template Haskell name (NameU),
      perhaps via newName, but did not bind it
      If that's it, then -ddump-splices might be useful
   |
99 | > deriveArgDict ''CatApi

Supporting an Either in this case is important for proper error handling of Token. Is the usage of deriveArgDict correct in this case? if yes, is this a bug?
if no, what is the proper way to achieve the Either like behavior?

Ghc 8.10 support

It would be great to have a version of constraints-extra which could be compiled with ghc-8.10.

Currently this is stuck on constraints for base and template-haskell.

Unnecessary dependency on Aeson

As far as I can tell from looking through the library source code, this package doesn't depend on Aeson, yet Aeson is still a dependency, which slows down compilation. The only use of Aeson is for the readme executable.

Seems not to want to compile on ghc 9.2.1

I'm getting:

[4 of 4] Compiling Data.Constraint.Extras.TH ( src/Data/Constraint/Extras/TH.hs, dist/build/Data/Constraint/Extras/TH.o, dist/build/Data/Constraint/Extras/TH.dyn_o )

src/Data/Constraint/Extras/TH.hs:55:22: error:
    • Couldn't match expected type ‘Pat’
                  with actual type ‘[Pat] -> Pat’
    • Probable cause: ‘ConP’ is applied to too few arguments
      In the first argument of ‘Match’, namely ‘(ConP name pat)’
      In the expression:
        Match
          (ConP name pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []
      In the expression:
        [Match
           (ConP name pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []]
   |
55 |           in [Match (ConP name pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []]
   |                      ^^^^^^^^^^^^^

src/Data/Constraint/Extras/TH.hs:55:32: error:
    • Couldn't match type ‘Pat’ with ‘Type’
      Expected: [Type]
        Actual: [Pat]
    • In the second argument of ‘ConP’, namely ‘pat’
      In the first argument of ‘Match’, namely ‘(ConP name pat)’
      In the expression:
        Match
          (ConP name pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []
   |
55 |           in [Match (ConP name pat) (NormalB $ AppE (VarE argDictName) (VarE v)) []]
   |             

Perhaps might want to switch via CPP on the TH version and treat the constructors differently.

deriveArgDict fails for types with many constructors

When trying to deriveArgDict for "large" types with many constructors, we can run into the limit of the maximum tuple arity (62) in GHC when collecting constraints.

A toy example of this is:

data C1 = C1
data C2 = C2
data C3 = C3
...
data C62 = C62
data C63 = C63

data Large a where
  L1 :: Large C1
  L2 :: Large C2
  L3 :: Large C3
  ...
  L62 :: Large C62
  L63 :: Large C63

deriveArgDict ''Large

Gives this error:

    • Constraint tuple arity too large: 63 (max arity = 62)
        Instead, use a nested tuple
    • In the type ‘(c_a3rNa C1, c_a3rNa C2, c_a3rNa C3, c_a3rNa C4,
                    c_a3rNa C5, c_a3rNa C6, c_a3rNa C7, c_a3rNa C8, c_a3rNa C9,
                    c_a3rNa C10, c_a3rNa C11, c_a3rNa C12, c_a3rNa C13, c_a3rNa C14,
                    c_a3rNa C15, c_a3rNa C16, c_a3rNa C17, c_a3rNa C18, c_a3rNa C19,
                    c_a3rNa C20, c_a3rNa C21, c_a3rNa C22, c_a3rNa C23, c_a3rNa C24,
                    c_a3rNa C25, c_a3rNa C26, c_a3rNa C27, c_a3rNa C28, c_a3rNa C29,
                    c_a3rNa C30, c_a3rNa C31, c_a3rNa C32, c_a3rNa C33, c_a3rNa C34,
                    c_a3rNa C35, c_a3rNa C36, c_a3rNa C37, c_a3rNa C38, c_a3rNa C39,
                    c_a3rNa C40, c_a3rNa C41, c_a3rNa C42, c_a3rNa C43, c_a3rNa C44,
                    c_a3rNa C45, c_a3rNa C46, c_a3rNa C47, c_a3rNa C48, c_a3rNa C49,
                    c_a3rNa C50, c_a3rNa C51, c_a3rNa C52, c_a3rNa C53, c_a3rNa C54,
                    c_a3rNa C55, c_a3rNa C56, c_a3rNa C57, c_a3rNa C58, c_a3rNa C59,
                    c_a3rNa C60, c_a3rNa C61, c_a3rNa C62, c_a3rNa C63)’
      In the type instance declaration for ‘Dep.ConstraintsFor’
      In the instance declaration for ‘Dep.ArgDict c_a3rNa Large’
     |
     | Dep.deriveArgDict ''Large
     | ^^^^^^^^^^^^^^^^^^^^^^^^^

Hackage haddock refresh

If there are no updates going out soon, is it possible to upload a new set of haddocks for the current version to hackage? If you're releasing a new version soon, then close this issue and I'll wait for the release.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.