How to put constraints on the associated data?

后端 未结 3 1353
温柔的废话
温柔的废话 2021-02-19 06:43

I would like to state that the associated data is always an instance of a certain class.

class (Context (Associated a b)) => Class a where
  data Associated a         


        
相关标签:
3条回答
  • 2021-02-19 06:54

    One idiomatic way is to create a Context1 class. Supposing we have

    class Context a where
        func :: a -> String
    

    we might generalize as:

    class Context1 f where
        func1 :: Context a => f a -> String
    

    Then you give a single instance for all Associateds:

    instance (Context1 (Associated a), Context b) => Context (Associated a b) where
        func = func1
    

    Now it is easy to write the class you want as

    instance Context1 (Associated a) => Class a where
        data Associated a :: * -> *
    

    and you can be sure that the given Context1 (Associated a) context ensures the desired forall b. Context b => Context (Associated a b) context.

    There are many examples of this pattern on Hackage, like Show1, Foldable1, and Traversable1.

    0 讨论(0)
  • I don't have GHC 7.0.3 available, but I think this should work with it.

    You could pass the dictionaries around manually like this (using Context = Show as an example):

    {-# LANGUAGE ScopedTypeVariables, TypeFamilies, ExistentialQuantification #-}
    
    data ShowDict a = Show a => ShowDict
    
    class Class a where
      data Associated a :: * -> *
    
      getShow :: ShowDict (Associated a b)
    
    -- Convenience function
    getShowFor :: Class a => Associated a b -> ShowDict (Associated a b)
    getShowFor _ = getShow
    
    showAssociated :: Class a => Associated a b -> String
    showAssociated a = 
      case getShowFor a of
        ShowDict -> -- Show (Associated a b) is made available by this pattern match 
          show a
    
    instance Class Int where
      data Associated Int b = Foo deriving Show
    
      getShow = ShowDict
    
    main = print $ showAssociated Foo
    

    This is somewhat similar to the function copying you propose, but advantages are:

    • Avoids repetition (of `Context`'s method signatures)
    • Having `Show Baz` in context is somewhat more powerful than just having a function for showing a `Baz`, since it allows you to call (library) functions which require `Show Baz`, or use implied instances like `Show [Baz]`:
    showAssociateds :: forall a b. Class a => [Associated a b] -> String
    showAssociateds as = 
      case getShow :: ShowDict (Associated a b) of
        ShowDict ->
          show as
    

    The main disadvantage is that using getShow always requires an explicit type signature (functions like getShowFor can mitigate this).

    0 讨论(0)
  • 2021-02-19 07:11

    As was pointed out by @SjoerdVisscher, using forall on the left side of => in a class or instance is actually not ok, at least not yet, though my specific example does work in ghc-7.4.


    This way it seems to work:

    {-# LANGUAGE FlexibleInstances    #-}
    {-# LANGUAGE TypeFamilies         #-}
    {-# LANGUAGE Rank2Types           #-}
    {-# LANGUAGE ConstraintKinds      #-}
    {-# LANGUAGE UndecidableInstances #-}
    
    class Context c where
      func1 :: c -> String
    
    class (forall b. Context (Associated a b)) => Class a where
      data Associated a :: * -> *
    
    newtype ClassTest = ClassTest { runClassTest :: String }
    
    instance (forall b. Context (Associated ClassTest b)) => Class ClassTest where
      data Associated ClassTest b = ClassTestAssoc b (b -> ClassTest)
    
    instance Context (Associated ClassTest b) where
      func1 (ClassTestAssoc b strFunc) = runClassTest $ strFunc b
    
    main = putStr . func1 $ ClassTestAssoc 37 (ClassTest . show)
    

    The extra forall b constraint in the instance seems a bit ugly and redundant, but apparently it's necessary.

    $ runghc-7.4.1 tFamConstraint0.hs
    37

    0 讨论(0)
提交回复
热议问题