Type families: top level vs. associated - haskell

I am just starting to learn type families. The GHC documentation states that top level and associated type families have the same functionality, but the code I am writing behaves differently in top level than it does when the families are associated. This compiles and runs fine:
{-# LANGUAGE TypeFamilies #-}
module Test where
-- type family R a
-- type instance R Maybe = Int
class C' a where
type R a
getInt' :: a Int
getBool' :: R a -> a Bool
instance C' Maybe where
type R Maybe = Int
getInt' = Just 3
getBool' i = Just $ i < 10
printer :: IO ()
printer = print $ (getBool' 5 :: Maybe Bool)
but this gives me a type error:
{-# LANGUAGE TypeFamilies #-}
module Test where
type family R a
type instance R Maybe = Int
class C' a where
-- type R a
getInt' :: a Int
getBool' :: R a -> a Bool
instance C' Maybe where
-- type R Maybe = Int
getInt' = Just 3
getBool' i = Just $ i < 10
printer :: IO ()
printer = print $ (getBool' 5 :: Maybe Bool)
These look identical to me; why is it that one compiles and the other doesn't?

The second one works if you annotate the kind:
type family R (a :: * -> *)
I don't think there's any reason why the right kind is only inferred for the associated type family.

Related

Is it possible to infer a type that is a reflection-like closure?

With the following "toy model" of Clash:
{-# LANGUAGE RankNTypes, KindSignatures, DataKinds, FlexibleContexts #-}
-- Simplified model of platform definitions
data Domain = DomSys | Dom25
data Signal (dom :: Domain)
data Clock (dom :: Domain)
class HiddenClock (dom :: Domain)
withClock :: Clock dom -> (HiddenClock dom => r) -> r
withClock _ _ = undefined
I would like to use withClock to close over the HiddenClock constraint inside a local where block. Suppose I have the following two toplevel definitions:
-- Simplified model of external standalone definitions
mainBoard :: (HiddenClock dom) => Signal dom -> Signal dom -> Signal dom -> (Signal dom, Signal dom)
mainBoard = undefined
peripherals :: (HiddenClock dom) => Signal dom -> Signal dom
peripherals = undefined
video
:: Clock domVid
-> Clock domSys
-> Signal domSys
-> Signal domSys
-> (Signal domVid, Signal domSys, Signal domSys)
video = undefined
then, I would like to write something like the following:
topEntity :: Clock Dom25 -> Clock DomSys -> Signal DomSys -> Signal Dom25
topEntity clkVid clkSys input = vga
where
(vga, vidRead, line) = video clkVid clkSys vidAddr vidWrite
(vidAddr, vidWrite) = withClock clkSys board
board = mainBoard vidRead line p
where
p = peripherals input
Unfortunately, GHC (at least as of 8.10.7) is unable to infer the correct type for board, which causes withClock clkSys board to not really close over the HiddenClock DomSys constriant:
• No instance for (HiddenClock 'DomSys)
arising from a use of ‘mainBoard’
• In the expression: mainBoard vidRead line p
In an equation for ‘board’:
board
= mainBoard vidRead line p
where
p = peripherals input
In an equation for ‘topEntity’:
topEntity clkVid clkSys input
= vga
where
(vga, vidRead, line) = video clkVid clkSys vidAddr vidWrite
(vidAddr, vidWrite) = withClock clkSys board
board
= mainBoard vidRead line p
where
p = peripherals input
|
38 | board = mainBoard vidRead line p
| ^^^^^^^^^^^^^^^^^^^^^^^^
• No instance for (HiddenClock 'DomSys)
arising from a use of ‘peripherals’
• In the expression: peripherals input
In an equation for ‘p’: p = peripherals input
In an equation for ‘board’:
board
= mainBoard vidRead line p
where
p = peripherals input
|
40 | p = peripherals input
| ^^^^^^^^^^^^^^^^^
This can be worked around by adding a type signature to board:
board :: (HiddenClock DomSys) => (Signal DomSys, Signal DomSys)
My question is: is it possible to change this code slightly, or fiddle with the exact type of withClock etc., to make this definition of topEntity typecheck without a type signature on the binding of board?
I don't think you can really infer this and I'm not entirely sure why you need to.
In Clash HiddenClock uses ImplicitParams under the hood. Currently, your board has no way of knowing where the clock is coming from.
You need to either pass the clock by value clkSys or explicitly write that the clock is needed at the type level with a HiddenClock constraint.
ImplicitParams don't really work like normal type class constraints. This HiddenClock isn't a constraint on the dom. And you can see that by the fact that HiddenClock 'DomSys is still needed as a constraint, even though it has no free variables.
Here is an example using plain Haskell (with ImplicitParams) of your issue:
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE RankNTypes #-}
module Temp where
withX :: Int -> ((?x :: Int) => r) -> r
withX x r =
let ?x = x
in r
somethingThanNeedsX :: (?x :: Int) => Int
somethingThanNeedsX = ?x + 2
foo :: Int
foo = bar
where
bar = withX 42 baz
baz = somethingThanNeedsX
And GHC tells me:
Orig.hs:19:11: error:
• Unbound implicit parameter (?x::Int)
arising from a use of ‘somethingThanNeedsX’
• In the expression: somethingThanNeedsX
In an equation for ‘baz’: baz = somethingThanNeedsX
In an equation for ‘foo’:
foo
= bar
where
bar = withX 42 baz
baz = somethingThanNeedsX
|
19 | baz = somethingThanNeedsX
|
In order to make this work, you either need to have withX in the definition of baz (explicitly passing x/the clock there) or be explicit about the ImplicitParams dependency. You don't need a full type signature if you don't want to, you just need the ImplicitParams constraint (using PartialTypeSignatures):
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PartialTypeSignatures #-}
module Temp where
withX :: Int -> ((?x :: Int) => r) -> r
withX x r =
let ?x = x
in r
somethingThanNeedsX :: (?x :: Int) => Int
somethingThanNeedsX = ?x + 2
foo :: Int
foo = bar
where
bar = withX 42 baz
baz :: (?x :: Int) => _
baz = somethingThanNeedsX
This now compiles just fine (with a warning that can be disabled with {-# OPTIONS_GHC -fno-warn-partial-type-signatures #-} if you really want):
Temp.hs:20:27: warning: [-Wpartial-type-signatures]
• Found type wildcard ‘_’ standing for ‘Int’
• In the type signature: baz :: (?x :: Int) => _
In an equation for ‘foo’:
foo
= bar
where
bar = withX 42 baz
baz :: (?x :: Int) => _
baz = somethingThanNeedsX
• Relevant bindings include foo :: Int (bound at Temp.hs:16:1)
|
20 | baz :: (?x :: Int) => _
|

DataKind Unions

I'm not sure if it is the right terminology, but is it possible to declare function types that take in an 'union' of datakinds?
For example, I know I can do the following:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
...
data Shape'
= Circle'
| Square'
| Triangle'
data Shape :: Shape' -> * where
Circle :: { radius :: Int} -> Shape Circle'
Square :: { side :: Int} -> Shape Square'
Triangle
:: { a :: Int
, b :: Int
, c :: Int}
-> Shape Triangle'
test1 :: Shape Circle' -> Int
test1 = undefined
However, what if I want to take in a shape that is either a circle or a square? What if I also want to take in all shapes for a separate function?
Is there a way for me to either define a set of Shape' kinds to use, or a way for me to allow multiple datakind definitions per data?
Edit:
The usage of unions doesn't seem to work:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
...
type family Union (a :: [k]) (r :: k) :: Constraint where
Union (x ': xs) x = ()
Union (x ': xs) y = Union xs y
data Shape'
= Circle'
| Square'
| Triangle'
data Shape :: Shape' -> * where
Circle :: { radius :: Int} -> Shape Circle'
Square :: { side :: Int} -> Shape Square'
Triangle
:: { a :: Int
, b :: Int
, c :: Int}
-> Shape Triangle'
test1 :: Union [Circle', Triangle'] s => Shape s -> Int
test1 Circle {} = undefined
test1 Triangle {} = undefined
test1 Square {} = undefined
The part above compiles
You can accomplish something like this in (I think) a reasonably clean way using a type family together with ConstraintKinds and PolyKinds:
type family Union (a :: [k]) (r :: k) :: Constraint where
Union (x ': xs) x = ()
Union (x ': xs) y = Union xs y
test1 :: Union [Circle', Triangle'] s => Shape s -> Int
test1 = undefined
The () above is the empty constraint (it's like an empty "list" of type class constraints).
The first "equation" of the type family makes use of the nonlinear pattern matching available in type families (it uses x twice on the left hand side). The type family also makes use of the fact that if none of the cases match, it will not give you a valid constraint.
You should also be able to use a type-level Boolean instead of ConstraintKinds. That would be a bit more cumbersome and I think it would be best to avoid using a type-level Boolean here (if you can).
Side-note (I can never remember this and I had to look it up for this answer): You get Constraint in-scope by importing it from GHC.Exts.
Edit: Partially disallowing unreachable definitions
Here is a modification to get it to (partially) disallow unreachable definitions as well as invalid calls. It is slightly more roundabout, but it seems to work.
Modify Union to give a * instead of a constraint, like this:
type family Union (a :: [k]) (r :: k) :: * where
Union (x ': xs) x = ()
Union (x ': xs) y = Union xs y
It doesn't matter too much what the type is, as long as it has an inhabitant you can pattern match on, so I give back the () type (the unit type).
This is how you would use it:
test1 :: Shape s -> Union [Circle', Triangle'] s -> Int
test1 Circle {} () = undefined
test1 Triangle {} () = undefined
-- test1 Square {} () = undefined -- This line won't compile
If you forget to match on it (like, if you put a variable name like x instead of matching on the () constructor), it is possible that an unreachable case can be defined. It will still give a type error at the call-site when you actually try to reach that case, though (so, even if you don't match on the Union argument, the call test1 (Square undefined) () will not type check).
Note that it seems the Union argument must come after the Shape argument in order for this to work (fully as described, anyway).
This is getting kind of awful, but I guess you could require a proof that it's either a circle or a square using Data.Type.Equality:
test1 :: Either (s :~: Circle') (s :~: Square') -> Shape s -> Int
Now the user has to give an extra argument (a "proof term") saying which one it is.
In fact you can use the proof term idea to "complete" bradm's solution, with:
class MyOpClass sh where
myOp :: Shape sh -> Int
shapeConstraint :: Either (sh :~: Circle') (sh :~: Square')
Now nobody can go adding any more instances (unless they use undefined, which would be impolite).
You could use typeclasses:
class MyOpClass sh where
myOp :: Shape sh -> Int
instance MyOpClass Circle' where
myOp (Circle r) = _
instance MyOpClass Square' where
myOP (Square s) = _
This doesn't feel like a particularly 'complete' solution to me - anyone could go back and add another instance MyOpClass Triangle' - but I can't think of any other solution. Potentially you could avoid this problem simply by not exporting the typeclass however.
Another solution I've noticed, though pretty verbose, is to create a kind that has a list of feature booleans. You can then pattern match on the features when restricting the type:
-- [circleOrSquare] [triangleOrSquare]
data Shape' =
Shape'' Bool
Bool
data Shape :: Shape' -> * where
Circle :: { radius :: Int} -> Shape (Shape'' True False)
Square :: { side :: Int} -> Shape (Shape'' True True)
Triangle
:: { a :: Int
, b :: Int
, c :: Int}
-> Shape (Shape'' False True)
test1 :: Shape (Shape'' True x) -> Int
test1 Circle {} = 2
test1 Square {} = 2
test1 Triangle {} = 2
Here, Triangle will fail to match:
• Couldn't match type ‘'True’ with ‘'False’
Inaccessible code in
a pattern with constructor:
Triangle :: Int -> Int -> Int -> Shape ('Shape'' 'False 'True),
in an equation for ‘test1’
• In the pattern: Triangle {}
In an equation for ‘test1’: test1 Triangle {} = 2
|
52 | test1 Triangle {} = 2
| ^^^^^^^^^^^
Unfortunately, I don't think you can write this as a record, which may be clearer and avoids the ordering of the features.
This might be usable in conjunction with the class examples for readability.

Difference between type family and partial newtype? (and partial data?)

I've had to interface two libraries where metadata is represented as a type parameter in one and as a record field in the other. I wrote an adaptor using a GADT. Here's a distilled version:
{-# LANGUAGE GADTs #-}
newtype TFId a = MkId a
data TFDup a = MkDup !a !a
data GADT tf where
ConstructorId :: GADT TFId
ConstructorDup :: GADT TFDup
main = do
f ConstructorId
f ConstructorDup
f :: GADT tf -> IO ()
f = _
This works. (May not be perfect; comments welcome, but that's not the question.)
It took me some time to get to this working state. My initial intuition was to use a type family for TFId, figuring: “GADT has kind (* -> *) -> *; in ConstructorDup TFDup has kind * -> *; so for ConstructorId I can use the following * -> * type family:”
{-# LANGUAGE TypeFamilies #-}
type family TFId a where TFId a = a
The type constructor does have the same kind * -> *, but GHC apparently won't have it in the same place:
error: …
The type family ‘TFId’ should have 1 argument, but has been given none
In the definition of data constructor ‘ConstructorId’
In the data type declaration for ‘GADT’
Well, if it says so…
I'm no sure I understand why it would make such a difference. No using type family stems without applying them? What's going on? Any other (better) way to do?
Injectivity.
type family F :: * -> *
type instance F Int = Bool
type instance F Char = Bool
here F Int ~ F Char. However,
data G (a :: *) = ...
will never cause G Int ~ G Char. These are guaranteed to be distinct types.
In universal quantifications like
foo :: forall f a. f a -> a
f is allowed to be G (injective) but not allowed to be F (not injective).
This is to make inference work. foo (... :: G Int) can be inferred to have type Int. foo (... :: F Int) is equivalent to foo (... :: Bool) which may have type Int, or type Char -- it's an ambiguous type.
Also consider foo True. We can't expect GHC to choose f ~ F, a ~ Int (or Char) for us. This would involve looking at all type families and see if Bool can be produced by any on them -- essentially, we would need to invert all the type families. Even if this were feasible, it would generate a huge amount of possible solutions, so it would be ambiguous.

Vector containing GADT

I'm just learning everything I can about ExistentialQuantification and GADTs and KindSignatures, etc. And to do that I try to come up with some small programs which help me to understand everything better.
Now I have this small snippet (which actually compiles, so you can try it on your own, requires vector and mtl packages) and would like to know whether it is at all possible to do what I am trying to accomplish or guide me to how to make it work
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE Rank2Types #-}
import Control.Monad.State.Lazy
import qualified Data.Vector as V
data MenuItem = ListS | ActionS | SliderS
data MenuItemReference (a :: MenuItem) (n :: *) where
MenuListSReference :: Int -> MenuItemReference ListS Int
MenuActionSReference :: Int -> MenuItemReference ActionS Int
MenuSliderSReference :: Int -> MenuItemReference SliderS Int
data MyState = MyState { vec :: forall a. V.Vector (MenuItemReference a Int) }
newMyState :: MyState
newMyState = MyState { vec = V.empty }
listRef :: MenuItemReference ListS Int
listRef = MenuListSReference 5
actionRef :: MenuItemReference ActionS Int
actionRef = MenuActionSReference 3
myComputation :: State MyState ()
myComputation = do
addItem listRef
addItem actionRef
return ()
addItem :: forall a. MenuItemReference a Int -> State MyState ()
addItem menuItemRef = do
s <- get
put (s { vec = (vec s) `V.snoc` menuItemRef })
main :: IO ()
main = do
print $ evalState myComputation newMyState
As you can see I'm trying to get a Vector of MenuItemReferences in it... What is it that I'm doing wrong because with what I have at the moment I get the error:
Couldn't match type ‘a’ with ‘a1’
‘a’ is a rigid type variable bound by
the type signature for
addItem :: MenuItemReference a Int -> State MyState ()
at Main.hs:34:19
‘a1’ is a rigid type variable bound by
a type expected by the context: V.Vector (MenuItemReference a1 Int)
at Main.hs:37:10
Expected type: MenuItemReference a1 Int
Actual type: MenuItemReference a Int
Relevant bindings include
menuItemRef :: MenuItemReference a Int (bound at Main.hs:35:9)
addItem :: MenuItemReference a Int -> State MyState ()
(bound at Main.hs:35:1)
In the second argument of ‘V.snoc’, namely ‘menuItemRef’
In the ‘vec’ field of a record
Could someone explain what is the reason behind the error and how I could approach (if at all possible) the thing I am trying to accomplish.
Why not just
data MenuItemReference =
MenuListSReference Int |
MenuActionSReference Int |
MenuSliderSReference Int
then?
The constructor used already annotates the value. You don't need to inject the phantom type, because the information is already there.
Besides, doing so would require enabling GHC ({-# LANGUAGE ImpredicativeTypes #-}) to actually support impredicative polymorphism to construct Vector [forall a. MenuItemReference a Int] and use it polymorphically. While it does support that, the support has been described as "fragile at best and broken at worst".
As a side note this nice blog post explains how we can get rid of impredicative types, using newtypes and RankNTypes instead. This does require you to introduce a layer of newtype, however.

Default type instances referring to each other

Is there a way to have default type instances defined in terms of each other? I'm trying to get something like this working:
{-# LANGUAGE DataKinds, KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
data Tag = A | B | C
class Foo (a :: *) where
type Bar a (b :: Tag)
type Bar a A = ()
type Bar a B = Bar a A
type Bar a C = Bar a A
instance Foo Int where
type Bar Int A = Bool
test :: Bar Int B
test = True
but this doesn't work:
Couldn't match type `Bar Int 'B' with `Bool'
In the expression: True
In an equation for `test': test = True
Note that this doesn't work either:
test :: Bar Int B
test = ()
Yes, default type instances can be defined in terms of each other (as you can see from your own example):
instance Foo Int where
-- So the default recursive definition will be used instead
-- type Bar Int A = Bool
test :: Bar Int B
test = ()
However when you redefine associated type synonym in your instance definition for Int you replace entire default 3-line defintion of Bar (and not just the type Bar a A = ()) with one line type Bar Int A = Bool which means Bar Int B and Bar Int C are no longer defined.
So I guess one of the ways to use recursive defaults the way you intended is to redefine specific synonyms instead (though it is rather verbose):
class Foo (a :: *) where
type Bar a (b :: Tag)
type Bar a A = BarA a
type Bar a B = BarB a
type BarA a
type BarA a = ()
type BarB a
type BarB a = Bar a A
-- This now works
instance Foo Int where
type BarA Int = Bool
test :: Bar Int B
test = True
Which can fall back to defaults:
-- As well as this one
instance Foo Int where
-- type BarA Int = Bool
test :: Bar Int B
test = ()

Resources