Couldn't match kind `*' against `#' - haskell

What the heck is going on here:
"Couldn't match kind `*' against `#'"
I was trying the following in GHCi using TemplateHaskell (ghci -XTemplateHaskell)
$(reify ''Show >>= dataToExpQ (const Nothing))
I was hoping to get an Exp out of this (which does have an instance of Show). I am doing this to insert information about haskell types in an application such that it is available as actual data, not as a string.
My goal is the following:
info :: Info
info = $(reify ''Show >>= dataToExpQ (const Nothing))
I really don't understand that error message, what is '#' anyway? If there is #, is there also # -> # or * -> #? Is it something that relates to kinds like kinds relate to types (though I would not know what that could be)?
Okay, so I do understand now that GHC has a hierarchy of kinds and that `#' is a special kind of unboxed types. All well and good, but why does this error pop up? Maybe unboxed types do not play well with genercis?
I'm not fully sure that this makes sense to me yet, since I would consider unboxed types being an optimazition performed by the compiler. I also thought that if an instance of Data exists, it needs to be there for all types that could possible be included in the data structure.
Upon further investigation I believe that Names pose the problem, is there a way to circumvent them in dataToExpQ? How to use that argument anyway?

You're right, it is the Names that cause the problem. More specifically, the problem is that the NameFlavour data type has unboxed integers in some of its fields.
There's a Haddock note on the Data NameFlavor instance that raises some red flags. And if you click through to the source, you'll see that the gfoldl definition essentially treats the unboxed integers like integers. (There's really not much else choice…) This ultimately causes the error you're seeing because dataToExpQ — having been tricked by the deceptive Data NameFlavour instance — builds an Exp term that applies NameU to an (Int :: *) when NameU actually expects an (unboxed) (Int# :: #).
So the problem is that the Data instance for NameFlavour disobeys the invariant assumed by dataToExpQ. But not to worry! This scenario falls squarely under the reason that dataToExpQ takes an argument: the argument lets us provide special treatment for troublesome types. Below, I do this in order to correctly reify the NameFlavour constructors that have unboxed integer fields.
There may be solutions out there for this, but I'm not aware of them, so I rolled up the following. It requires a separate module because of the TH staging restriction.
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MagicHash #-}
module Stage0 where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import GHC.Types (Int(I#))
import GHC.Prim (Int#)
unboxed :: Int# -> Q Exp
unboxed i = litE $ intPrimL $ toInteger $ I# i -- TH does support unboxed literals
nameFlavorToQExp :: NameFlavour -> Maybe (Q Exp)
nameFlavorToQExp n = case n of
NameU i -> Just [| NameU $(unboxed i) |]
NameL i -> Just [| NameL $(unboxed i) |]
_ -> Nothing
And then the following compiles for me.
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Generics.SYB
import Stage0
info :: Info
info = $(reify ''Show >>= dataToExpQ (mkQ Nothing nameFlavorToQExp))
CAVEAT PROGRAMMER The unboxed integers we're bending over backwards for here correspond to "uniques" that GHC uses internally. They are not necessarily expected to be serialized. Depending on how you're using the resulting Info value, this may cause explosions.
Also note when reifying Show, you're also reifying every instance of Show that's in scope.
There's a lot of them — this generates a pretty big syntax term.
As the documentation says, these instances do not include the method definitions.
HTH.

Related

When should TypeApplications be preferred over simple :: signatures or ScopedTypeVariables?

Considering this simple example of ambiguous type inference:
#! /usr/bin/env stack
{- stack runghc -}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
main :: IO ()
main = do
-- This will fail to compile without additional type info
-- let w = read "22"
-- print w
-- My go-to for this is type signatures in the expressions
let x = read "33" :: Integer
print x
-- Another possibility is ScopedtypeVariables
let y :: Integer = read "44"
print y
-- How does TypeApplications differ from the code above? When should this be chosen instead?
let z = read #Integer "55"
print z
My question is, in cases like this, is there an advantage to using TypeApplications?
In almost all cases, it is an aesthetic choice only. I make the following additional comments for your consideration:
In all cases, if a thing typechecks with some collection of type signatures, there is a corresponding collection of type applications that also causes that term to typecheck (and with the same choices of instance dictionaries, etc.).
In cases where either a signature or an application can be used, the code produced by GHC will be identical.
Some ambiguous types cannot be resolved via signatures, and type applications must be used. For example, foo :: (Monoid a, Monoid b) => b cannot be given a type signature that determines a. (This bullet motivates the "almost" in the first sentence of this answer. No other bullet motivates the "almost".)
Type applications are frequently syntactically lighter than type signatures. For example, when the type is long, or a type variable is mentioned several times. Some comparisons:
showsPrec :: Int -> Bool -> String -> String
showsPrec #Bool
sortOn :: Ord b => (Int -> b) -> [Int] -> [Int]
sortOn #Int
Sometimes it is possible to shuffle the type signature around to a different subterm so that you need only give a short signature with little repetition. But then again... sometimes not.
Sometimes, the signature or application is intended to convey some information to the reader or encourage a certain way of thinking about a piece of code (i.e. is not strictly for compiler consumption). If part of that information involves attaching the annotation in a specific code location, your options may be somewhat constrained.

How can I turn a [TExp a] into a TExp [a], or otherwise apply refineTH to multiple values programatically?

I've been using refined for refinement types in Haskell recently, and have encountered a major usability problem. I can't figure out how to refine an entire list of values at compile time.
For example I can write:
{-# LANGUAGE TemplateHaskell #-}
import Refined
oneToThree :: [Refined Positive Int]
oneToThree = [$$(refineTH 1), $$(refineTH 2), $$(refineTH 3)]
But I can't do this precludes the ability of using range syntax, because Refined doesn't (for good reason) have an instance for Enum.
I would like to be able to do something like
oneToThree :: [Refined Positive Int]
oneToThree = $$(traverse refineTH [1..3])
but I can't get this to compile because I can't lift [TExp (Refined Positive Int)] into TExp [Refined Positive Int].
Is there template haskell magic that I missing that will let me do this?
Would also be open to suggestions for better lightweight refinement type libraries if someone has a suggestion.
sequenceQTExpList :: [Q (TExp a)] -> Q (TExp [a])
sequenceQTExpList [] = [|| [] ||]
sequenceQTExpList (x:xs) = [|| $$(x) : $$(sequenceQTExpList xs) ||]
Then use it as
$$(sequenceQTExpList $ map refineTH [1..3])
You're right that it feels like a traverse. The type is a bit off, though, with the extra Qs floating around. I don't see anything offhand that lets you combine those layers usefully.
Unfortunately, a lot of the mechanism used there is TH syntax rather than functions. There just isn't an obvious way to do both the lifting and the splicing as functions, so you're stuck writing bespoke helpers for each container type instead of getting to use Traversable. It's an interesting problem. If there's a clean solution, it'd have a good chance of making it into a future version of template Haskell if it was brought up to the maintainers. But I just don't see it right now.
This works (it needs to be in a different file than you use it in because of the stage restriction, though):
import Language.Haskell.TH.Syntax (Exp(ListE), TExp(TExp))
makeTypedTHList :: [TExp a] -> TExp [a]
makeTypedTHList xs = TExp $ ListE [x | TExp x <- xs]
You'd then use it like this:
{-# LANGUAGE TemplateHaskell #-}
import Refined
import AboveCodeInSeparateModuleBecauseOfStageRestriction (makeTypedTHList)
oneToThree :: [Refined Positive Int]
oneToThree = $$(makeTypedTHList <$> traverse refineTH [1..3])
However, calling the TExp constructor yourself subverts some of the safety of typed Template Haskell (although I think this particular case is safe). Ideally, I'd prefer an approach that didn't require doing that, but I can't think of one.

Limit a number to a range (Haskell)

I am exposing a function which takes two parameters, one is a minimum bound and the other is a maximum bound. How can I ensure, using types, that for example the minimum bound is not greater than the maximum bound?
I want to avoid creating a smart constructor and returning a Maybe because it would make the whole usage more cumbersome.
Thank you
This doesn't exactly answer your question, but one approach that sometimes works is to change your interpretation of your type. For example, instead of
data Range = {lo :: Integer, hi :: Integer}
you could use
data Range = {lo :: Integer, size :: Natural}
This way, there's no way to represent an invalid range.
This solution uses dependent types (and might be too heavyweight, check if dfeuer's answer is enough for your needs).
The solution makes use of the GHC.TypeLits module from base, and also of the typelits-witnesses package.
Here is a difference function that takes two integer arguments (known statically) and complains at compile-time when the first number is greater than the second:
{-# language TypeFamilies #-}
{-# language TypeOperators #-}
{-# language DataKinds #-}
{-# language ScopedTypeVariables #-}
import GHC.TypeLits
import GHC.TypeLits.Compare
import Data.Type.Equality
import Data.Proxy
import Control.Applicative
difference :: forall n m. (KnownNat n,KnownNat m,n <= m)
=> Proxy n
-> Proxy m
-> Integer
difference pn pm = natVal pm - natVal pn
We can check it from GHCi:
ghci> import Data.Proxy
ghci> :set -XTypeApplications
ghci> :set -XDataKinds
ghci> difference (Proxy #2) (Proxy #7)
5
ghci> difference (Proxy #7) (Proxy #2)
** TYPE ERROR **
But what if we want to use the function with values determined at run time? Say, values that we read from console, or from a file?
main :: IO ()
main = do
case (,) <$> someNatVal 2 <*> someNatVal 7 of
Just (SomeNat proxyn,SomeNat proxym) ->
case isLE proxyn proxym of
Just Refl -> print $ difference proxyn proxym
Nothing -> error "first number not less or equal"
Nothing ->
error "could not bring KnownNat into scope"
In this case, we use functions like someNatVal and isLE. These functions might fail with Nothing. If they succeed, however, they return a value that "witnesses" some constraint. And by pattern-matching on the witness, we bring that constraint into scope (this works because the witness is a GADT).
In the example, the Just (SomeNat proxyn,SomeNat proxym) pattern match brings KnownNat constraints for the two arguments into scope. And the Just Refl pattern match brings the n <= m constraint into scope. Only then we can call our difference function.
So, in a way, we have shifted all the busywork of ensuring that the arguments satisfy the required preconditions out of the function itself.
What you're asking for is dependent types. There is a nice tutorial on it in
https://www.schoolofhaskell.com/user/konn/prove-your-haskell-for-great-safety/dependent-types-in-haskell
Although I don't know how friendly it will be. Do note that dependent typing was improved in GHC 8.0 but I have no experience in that area. I would make sure you're comfortable using template Haskell if you don't want it to be cumbersome.
You needn't invoke the Maybe type to take advantage of 'smart constructors'. If you like, you may accept constructors of either form (min,max) or (max,min) and still create a data type which correctly interprets which is which.
For instance, you could make a little module:
module RangeMinMax (
Range,
makeRange
)
where
data Range = Range (Integer,Integer)
deriving Show
makeRange a b = Range (min a b, max a b)
And now when you create a Range using makeRange, the 2-tuple will automatically be arranged so it's in the form (min,max). Note that the constructor for Range is not exported, so the user of the module is unable to create an invalid Range-- you just need to make sure that you create valid ones in the this module.

Which dictionary does GHC choose when more than one is in scope?

Consider the following example:
import Data.Constraint
class Bar a where
bar :: a -> a
foo :: (Bar a) => Dict (Bar a) -> a -> a
foo Dict = bar
GHC has two choices for the dictionary to use when selecting a Bar instance in foo: it could use the dictionary from the Bar a constraint on foo, or it could use the runtime Dict to get a dictionary. See this question for an example where the dictionaries correspond to different instances.
Which dictionary does GHC use, and why is it the "correct" choice?
It just picks one. This isn't the correct choice; it's a pretty well-known wart. You can cause crashes this way, so it's a pretty bad state of affairs. Here is a short example using nothing but GADTs that demonstrates that it is possible to have two different instances in scope at once:
-- file Class.hs
{-# LANGUAGE GADTs #-}
module Class where
data Dict a where
Dict :: C a => Dict a
class C a where
test :: a -> Bool
-- file A.hs
module A where
import Class
instance C Int where
test _ = True
v :: Dict Int
v = Dict
-- file B.hs
module B where
import Class
instance C Int where
test _ = False
f :: Dict Int -> Bool
f Dict = test (0 :: Int)
-- file Main.hs
import TestA
import TestB
main = print (f v)
You will find that Main.hs compiles just fine, and even runs. It prints True on my machine with GHC 7.10.1, but that's not a stable outcome. Turning this into a crash is left to the reader.
GHC just picks one, and this is the correct choice. Any two dictionaries for the same constraint are supposed to be equal.
OverlappingInstances and IncoherentInstances are basically equivalent in destructive power; they both lose instance coherence by design (any two equal constraints in your program being satisfied by the same dictionary). OverlappingInstances gives you a little more ability to work out which instances will be used on a case-by-case basis, but this isn't that useful when you get to the point of passing around Dicts as first class values and so on. I would only consider using OverlappingInstances when I consider the overlapping instances extensionally equivalent (e.g., a more efficient but otherwise equal implementation for a specific type like Int), but even then, if I care enough about performance to write that specialized implementation, isn't it a performance bug if it doesn't get used when it could be?
In short, if you use OverlappingInstances, you give up the right to ask the question of which dictionary will be selected here.
Now it's true that you can break instance coherence without OverlappingInstances. In fact you can do it without orphans and without any extensions other than FlexibleInstances (arguably the problem is that the definition of "orphan" is wrong when FlexibleInstances is enabled). This is a very long-standing GHC bug, which hasn't been fixed in part because (a) it actually can't cause crashes directly as far as anybody seems to know, and (b) there might be a lot of programs that actually rely on having multiple instances for the same constraint in separate parts of the program, and that might be hard to avoid.
Getting back to the main topic, in principle it's important that GHC can select any dictionary that it has available to satisfy a constraint, because even though they are supposed to be equal, GHC might have more static information about some of them than others. Your example is a little bit too simple to be illustrative but imagine that you passed an argument to bar; in general GHC doesn't know anything about the dictionary passed in via Dict so it has to treat this as a call to an unknown function, but you called foo at a specific type T for which there was a Bar T instance in scope, then GHC would know that the bar from the Bar a constraint dictionary was T's bar and could generate a call to a known function, and potentially inline T's bar and do more optimizations as a result.
In practice, GHC is currently not this smart and it just uses the innermost dictionary available. It would probably be already better to always use the outermost dictionary. But cases like this where there are multiple dictionaries available are not very common, so we don't have good benchmarks to test on.
Here's a test:
{-# LANGUAGE FlexibleInstances, OverlappingInstances, IncoherentInstances #-}
import Data.Constraint
class C a where foo :: a -> String
instance C [a] where foo _ = "[a]"
instance C [()] where foo _ = "[()]"
aDict :: Dict (C [a])
aDict = Dict
bDict :: Dict (C [()])
bDict = Dict
bar1 :: String
bar1 = case (bDict, aDict :: Dict (C [()])) of
(Dict,Dict) -> foo [()] -- output: "[a]"
bar2 :: String
bar2 = case (aDict :: Dict (C [()]), bDict) of
(Dict,Dict) -> foo [()] -- output: "[()]"
GHC above happens to use the "last" dictionary which was brought into scope. I wouldn't rely on this, though.
If you limit yourself to overlapping instances, only, then you wouldn't be able to bring in scope two different dictionaries for the same type (as far as I can see), and everything should be fine since the choice of the dictionary becomes immaterial.
However, incoherent instances are another beast, since they allow you to commit to a generic instance and then use it at a type which has a more specific instance. This makes it very hard to understand which instance will be used.
In short, incoherent instances are evil.
Update: I ran some further tests. Using only overlapping instances and an orphan instance in a separate module you can still obtain two different dictionaries for the same type. So, we need even more caveats. :-(

Is there a way to define an existentially quantified newtype in GHC Haskell?

Is it possible in (GHC) Haskell to define an existentially-quantified newtype? I understand that if type classes are involved it can't be done in a dictionary-passing implementation, but for my purposes type-classes are not needed. What I'd really like to define is this:
newtype Key t where Key :: t a -> Key t
But GHC does not seem to like it. Currently I'm using data Key t where Key :: !(t a) -> Key t. Is there any way (perhaps just using -funbox-strict-fields?) to define a type with the same semantics and overhead as the newtype version above? My understanding is that even with strict fields unboxed there will still be an extra tag word, though I could be totally wrong there.
This is not something that's causing me any noticeable performance issues. It just surprised me that the newtype was not allowed. I'm a naturally curious person, so I can't help wondering whether the version I have is being compiled to the same representation or whether any equivalent type could be defined which would be.
No, according to GHC:
A newtype constructor cannot have an existential context
However, data is just fine:
{-# LANGUAGE ExistentialQuantification #-}
data E = forall a. Show a => E a
test = [ E "foo"
, E (7 :: Int)
, E 'x'
]
main = mapM_ (\(E e) -> print e) test
E.g.
*Main> main
"foo"
7
'x'
Logically, you do need the dictionary (or tag) allocated somewhere. And that doesn't make sense if you erase the constructor.
Note: You can't unbox functions though, as you seem to be hinting at, nor polymorphic fields.
Is there any way (perhaps just using -funbox-strict-fields?) to define a type with the same semantics and overhead as the newtype version above?
Removing the -XGADTs helps me think about this:
{-# LANGUAGE ExistentialQuantification #-}
data Key t = forall a. Key !(t a)
As in, Key (Just 'x') :: Key Maybe
So you want to guarantee the Key constructor is erased.
Here's the code in GHC for type checking the constraints on newtype:
-- Checks for the data constructor of a newtype
checkNewDataCon con
= do { checkTc (isSingleton arg_tys) (newtypeFieldErr con (length arg_tys))
-- One argument
; checkTc (null eq_spec) (newtypePredError con)
-- Return type is (T a b c)
; checkTc (null ex_tvs && null eq_theta && null dict_theta) (newtypeExError con)
-- No existentials
; checkTc (not (any isBanged (dataConStrictMarks con)))
(newtypeStrictError con)
-- No strictness
We can see why ! won't have any effect on the representation, since it contains polymorphic components, so needs to use the universal representation. And unlifted newtype doesn't make sense, nor non-singleton constructors.
The only thing I can think of is that, like for record accessors for existentials, the opaque type variable will escape if the newtype is exposed.
I don't see any reason it couldn't be made to work, but perhaps ghc has some internal representation issues with it.

Resources