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 :: * -> *
instance Context (Associated a b) where
func1 = error "func1"
However, the free variable b
that is not in scope prevents me from this. One of the solutions is to copy class functions from Context
, but it looks ugly.
class Class a where
data Associated a :: * -> *
-- duplicate all functions from class Context
contextFunc1 :: Associated a b -> String
instance Class a => Context (Associated a b) where
func1 = contextFunc1
Is there an idiomatic way to put constraints on associated data type which has variables not mentioned in head?
edit: I would like to keep compatibility with GHC 7.0.3
The basic syntax of ALTER TABLE to ADD UNIQUE CONSTRAINT to a table is as follows. ALTER TABLE table_name ADD CONSTRAINT MyUniqueConstraint UNIQUE(column1, column2...); The basic syntax of an ALTER TABLE command to ADD CHECK CONSTRAINT to a table is as follows.
Constraints are the rules enforced on the data columns of a table. These are used to limit the type of data that can go into a table. This ensures the accuracy and reliability of the data in the database. Constraints could be either on a column level or a table level.
A constraint can be created at table creation using CREATE TABLE, or added to a table later using ALTER TABLE: Single-column constraints can be created inline as part of the column definition. Multi-column constraints must be created in a separate, i.e. out-of-line, clause that specifies the columns in the constraint.
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
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:
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).
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With