Can I export constructors along with a type alias? - haskell

I have a data type data Foo a b = Bar a b that I use internally in a library.
I also have an alias for one of its more common concrete forms: type Bar = Foo Int Int.
Is there a way to export the Bar type, but not the Foo type from my library?
I'd like to do:
module Quux (
Bar(Bar)
) where
But when I attempt this I get the error:
The export item ‘Bar(Bar)’
attempts to export constructors or class methods that are not visible here
The below would work, except I'd rather not export the Foo type at all:
module Quux (
Bar
, Foo(..)
) where

This isn't possible in Haskell 2010, but is possible in GHC.
In Haskell 2010, you can only export constructors as part of a data type:
Data constructors cannot be named in export lists except as subordinate names [the Cᵢ in T(C₁,C₂)], because they cannot otherwise be distinguished from type constructors. [Haskell 2010 Report, §5.2 "Export Lists", #2]
In GHC (version 7.8 or later), however, you can use the PatternSynonyms language extension to accomplish this: with that turned on, you can qualify constructors in export lists with pattern. So, for instance, your desired example would be
{-# LANGUAGE PatternSynonyms #-}
module Quux (Bar, pattern Bar) where
data Foo a b = Bar a b
type Bar = Foo Int Int
The pattern Bar in the export list specifies the constructor, and the unadorned Bar specifies the type synonym.
In addition, if you think the unadorned Bar is confusing/ambiguous, you can use the ExplicitNamespaces extension (in version 7.6 or later) to enable prefixing type constructors with type, similarly:
{-# LANGUAGE ExplicitNamespaces, PatternSynonyms #-}
module Quux (type Bar, pattern Bar) where
data Foo a b = Bar a b
type Bar = Foo Int Int
From the documentation, about exporting constructors with pattern:
[W]ith -XPatternSynonyms you can prefix the name of a data constructor in an import or export list with the keyword pattern, to allow the import or export of a data constructor without its parent type constructor [GHC 7.10 Users Manual, §7.3.26.4 "Explicit namespaces in import/export"]
and
You may also use the pattern keyword in an import/export specification to import or export an ordinary data constructor. For example:
import Data.Maybe( pattern Just )
would bring into scope the data constructor Just from the Maybe type, without also bringing the type constructor Maybe into scope. [GHC 7.10 Users Manual, §7.3.9.2 "Import and export of pattern synonyms"]
Plus, for exporting types with type:
The -XExplicitNamespaces extension allows you to prefix the name of a type constructor in an import or export list with "type" to disambiguate… [GHC 7.10 Users Manual, §7.3.26.4 "Explicit namespaces in import/export"]
That said, I am inclined to agree with dfeuer here – there's a reason the report disallows this. Type signatures that are impossible to write down – e.g., Bar :: a -> b -> Quux.Foo a b – are a bit maddening. But the type synonym does help with that; just make sure your documentation is thorough :-)

You can export Bar type simply by module Quux (Bar) where ..., though you will not be able to construct any Bars.
If you also need the constructor, you may use similar technique to smart constructors, that is create a helper functions which creates Bars and export that one:
module Quux (Bar, bar) where
data Foo a b = Foo a b
type Bar = Foo Int Int
bar :: Int -> Int -> Bar
bar = Foo
then
\> let b = bar 1 2
\> :type b
b :: Bar
\> let f = Foo 1 2
<interactive>:9:9: Not in scope: data constructor ‘Foo’

Why do you want to do this? No, don't bother answering. Don't do this. Whatever you think it will accomplish, it will not. What you can do, however, is use a newtype (note that I changed the names a bit):
newtype Bar = _Bar (Foo Int Int)
data Foo a b = Foo a b
Now you can use pattern synonyms to make Bar user-friendly:
{-# LANGUAGE PatternSynonyms #-}
module Whatever (Bar, pattern Bar)
pattern Bar a b = _Bar (Foo a b)
There's a bit of weirdness having to use the pattern keyword to import the synonym, but oh well. Unlike your approach, the end user has access to a proper first-class type and not just a synonym. And they can't see anything of Foo.

Related

Is there a way to refer directly to typeclass instances in Haskell?

The benefit of this could be to store certain metadata about the type in a canonical location. Sometimes, it isn't convenient to have a value of the type before using some instance methods on it; For instance if I have:
class Foo a where
foo :: String
foo = "Foo"
This is not actually valid Haskell. Instead it seems I have to have something like:
class Foo a where
foo :: a -> String
foo = const "Foo"
and now foo will actually have type Foo a => a -> String, but I would actually like to be able to do something like having a foo with type Instance Foo -> String. For this to be useful in some contexts, it might be also necessary to iterate over all (in-scope?) instances, or in other contexts, to be able to specifically materialize an instance for a given type.
I guess the issue is that instances and typeclasses are not first-class entities in Haskell?
The "old school" way of doing it is providing a "dummy" parameter whose purpose is nothing but helping the compiler find the appropriate instance. In this world, your class would look something like:
data Dummy a = Dummy
class Foo a where
foo :: Dummy a -> String
-- usage:
boolFoo = foo (Dummy :: Dummy Bool)
In fact, this trick was so ubiquitous that the Dummy type was semi-standardized as Data.Proxy.
But in modern GHC there is a better way: TypeApplications.
With this extension enabled, you can just straight up specify the type when calling the class method:
class Foo a where
foo :: String
boolFoo = foo #Bool
(this doesn't only work for class methods; it will work with any generic function, but be careful with the order of type parameters!)
You may also need to enable AllowAmbiguousTypes in order to declare such class. Though I'm not sure I remember this correctly, and I don't have a computer handy to check.
The old way (which I still prefer) is to use a proxy.
import Data.Proxy
class Foo a where
foo :: Proxy a -> String
instance Foo FancyPants where
foo _ = "a fancypants instance"
fooString :: String
fooString = foo (Proxy :: Proxy FancyPants)
So we didn't actually need a value of type FancyPants to use foo, all we needed is a value of Proxy FancyPants -- but you can create proxies of any type you want. This can be done in a polymorphic context too; usually it requires the use of the ScopedTypeVariables extension.
The new way is to use the TypeApplications and AllowAmbiguousTypes extension:
{-# LANGUAGE TypeApplications, AllowAmbiguousTypes #-}
class Foo a where
foo :: String
instance Foo FancyPants where
foo = "a fancypants instance"
fooString :: String
fooString = foo #FancyPants
Which looks nicer, but working with it in practice tends to be more irritating for a reason I can't quite put my finger on.
Did that answer the question?

Pattern bindings for existential constructors

While writing Haskell as a programmer that had exposure to Lisp before, something odd came to my attention, which I failed to understand.
This compiles fine:
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Show a => Foo { getFoo :: a }
showfoo :: Foo -> String
showfoo Foo{getFoo} = do
show getFoo
whereas this fails:
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Show a => Foo { getFoo :: a }
showfoo :: Foo -> String
showfoo foo = do
let Foo{getFoo} = foo
show getFoo
To me it's not obvious why the second snippet fails.
The question would be:
Do I miss something or stems this behaviour from the fact that haskell is not homoiconic?
My reasoning is, given that:
Haskell needs to implement record pattern matching as a compiler extension, because of it's choice to use syntax rather than data.
Matching in a function head or in a let clause are two special cases.
It is difficult to understand those special cases, as they cannot be either implemented nor looked up directly in the language itself.
As an effect of this, consistent behaviour throughout the language is not guaranteed. Especially together with additional compiler extensions, as per example.
ps: compiler error:
error:
• My brain just exploded
I can't handle pattern bindings for existential or GADT data constructors.
Instead, use a case-expression, or do-notation, to unpack the constructor.
• In the pattern: Foo {getFoo}
In a pattern binding: Foo {getFoo} = foo
In the expression:
do { let Foo {getFoo} = foo;
show getFoo }
edit:
A different compiler version gives this error for the same problem
* Couldn't match expected type `p' with actual type `a'
because type variable `a' would escape its scope
This (rigid, skolem) type variable is bound by
a pattern with constructor: Foo :: forall a. Show a => a -> Foo
Do I miss something or stems this behaviour from the fact that haskell is not homoiconic?
No. Homoiconicity is a red herring: every language is homoiconic with its source text and its AST1, and indeed, Haskell is implemented internally as a series of desugaring passes between various intermediate languages.
The real problem is that let...in and case...of just have fundamentally different semantics, which is intentional. Pattern-matching with case...of is strict, in the sense that it forces the evaluation of the scrutinee in order to choose which RHS to evaluate, but pattern bindings in a let...in form are lazy. In that sense, let p = e1 in e2 is actually most similar to case e1 of ~p -> e2 (note the lazy pattern match using ~!), which produces a similar, albeit distinct, error message:
ghci> case undefined of { ~Foo{getFoo} -> show getFoo }
<interactive>:5:22: error:
• An existential or GADT data constructor cannot be used
inside a lazy (~) pattern
• In the pattern: Foo {getFoo}
In the pattern: ~Foo {getFoo}
In a case alternative: ~Foo {getFoo} -> show getFoo
This is explained in more detail in the answer to Odd ghc error message, "My brain just exploded"?.
1If this doesn’t satisfy you, note that Haskell is homoiconic in the sense that most Lispers use the word, since it supports an analog to Lisp’s quote operator in the form of [| ... |] quotation brackets, which are part of Template Haskell.
I thought about this a bit and albeit the behaviour seems odd at first, after some thinking I guess one can justify it perhaps thus:
Say I take your second (failing) example and after some massaging and value replacements I reduce it to this:
data Foo = forall a. Show a => Foo { getFoo :: a }
main::IO()
main = do
let Foo x = Foo (5::Int)
putStrLn $ show x
which produces the error:
Couldn't match expected type ‘p’ with actual type ‘a’ because type variable ‘a’ would escape its scope
if the pattern matching would be allowed, what would be the type of x? well.. the type would be of course Int. However the definition of Foo says that the type of the getFoo field is any type that is an instance of Show. An Int is an instance of Show, but it is not any type.. it is a specific one.. in this regard, the actual specific type of the value wrapped in that Foo would become "visible" (i.e. escape) and thus violate our explicit guarantee that forall a . Show a =>...
If we now look at a version of the code that works by using a pattern match in the function declaration:
data Foo = forall a . Show a => Foo { getFoo :: !a }
unfoo :: Foo -> String
unfoo Foo{..} = show getFoo
main :: IO ()
main = do
putStrLn . unfoo $ Foo (5::Int)
Looking at the unfoo function we see that there is nothing there saying that the type inside of the Foo is any specific type.. (an Int or otherwise) .. in the scope of that function all we have is the original guarantee that getFoo can be of any type which is an instance of Show. The actual type of the wrapped value remains hidden and unknowable so there are no violations of any type guarantees and happiness ensues.
PS: I forgot to mention that the Int bit was of course an example.. in your case, the type of the getFoo field inside of the foo value is of type a but this is a specific (non existential) type to which GHC's type inference is referring to (and not the existential a in the type declaration).. I just came up with an example with a specific Int type so that it would be easier and more intuitive to understand.

How to handle functions of a multi-parameter typeclass, who not need every type of the typeclass?

I've defined a typeclass similar to an interface with a bunch of functions required for my program. Sadly, it needs multiple polymorphic types, but not every function of this multi-parameter typeclass needs every type. GHC haunts me with undeduceable types and i can't get the code running.
A reduced example:
{-# LANGUAGE MultiParamTypeClasses #-}
class Foo a b where
-- ...
bar :: a -> ()
baz :: Foo a b => a -> ()
baz = bar
GHC says
Possible fix: add a type signature that fixes these type variable(s)
How can I do this for b? Especially when I want to keep b polymorphic. Only an instance of Foo should define what this type is.
This is impossible.
The underlying problem is that a multiparameter type class depends on every type parameter. If a particular definition in the class doesn't use every type parameter, the compiler will never be able to know what instance you mean, and you'll never even be able to specify it. Consider the following example:
class Foo a b where
bar :: String -> IO a
instance Foo Int Char where
bar x = return $ read x
instance Foo Int () where
bar x = read <$> readFile x
Those two instances do entirely different things with their parameter. The only way the compiler has to select one of those instances is matching both type parameters. But there's no way to specify what the type parameter is. The class is just plain broken. There's no way to ever call the bar function, because you can never provide enough information for the compiler to resolve the class instance to use.
So why is the class definition not rejected by the compiler? Because you can sometimes make it work, with the FunctionalDependencies extension.
If a class has multiple parameters, but they're related, that information can sometimes be added to the definition of the class in a way that allows a class member to not use every type variable in the class's definition.
class Foo a b | a -> b where
bar :: String -> IO a
With that definition (which requires the FunctionalDependencies extension), you are telling the compiler that for any particular choice of a, there is only one valid choice of b. Attempting to even define both of the above instances would be a compile error.
Given that, the compiler knows that it can select the instance of Foo to use based only on the type a. In that case, bar can be called.
Splitting it in smaller typeclasses might be sufficient.
{-# LANGUAGE MultiParamTypeClasses #-}
class Fo a => Foo a b where
-- ...
foo :: a -> b -> ()
class Fo a where
bar :: a -> ()
baz :: Foo a b => a -> ()
baz = bar
Assuming you really want to use more than one instance for a given a (and so cannot use functional dependencies as others mentioned), one possibility which may or may not be right for you is to use a newtype tagged with a "phantom" type used only to guide type selection. This compiles:
{-# LANGUAGE MultiParamTypeClasses #-}
newtype Tagged t a = Tagged { unTagged :: a } -- Also defined in the tagged package
-- on Hackage
class Foo a b where
bar :: Tagged b a -> ()
baz :: Foo a b => Tagged b a -> ()
baz = bar
Then you will be able to wrap your values in such a way that you can give an explicit type annotation to select the right instance.
Another way of refactoring multi-parameter type classes when they get awkward is to use the TypeFamilies extension. Like FunctionalDependencies, this works well when you can reframe your class as having only a single parameter (or at least, fewer parameter), with the other types that are different from instance to instance being computed from the actual class parameters.
Generally I've found whenever I thought I needed a multi-parameter type class, the parameters almost always varied together rather than varying independently. In this situation it's much easier to pick one as "primary" and use some system for determining the others from it. Functional dependencies can do this as well as type families, but many find type families a lot easier to understand.
Here's an example:
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
class Glue a where
type Glued a
glue :: a -> a -> Glued a
instance Glue Char where
type Glued Char = String
glue x y = [x, y]
instance Glue String where
type Glued String = String
glue x y = x ++ y
glueBothWays :: Glue a => a -> a -> (Glued a, Glued a)
glueBothWays x y = (glue x y, glue y x)
The above declares a class Glue of types that can be glued together with the glue operation, and that have a corresponding type which is the result of the "gluing".
I then declared a couple of instances; Glued Char is String, Glued String is also just String.
Finally I wrote a function to show how you use Glued when you're being polymorphic over the instance of Glue you're using; basically you "call" Glued as a function in your type signatures; this means glueBothWays doesn't "know" what type Glued a is, but it knows how it corresponds to a. You can even use Glued Char as a type, if you know you're gluing Chars but don't want to hard-code the assumption that Glued Char = String.

Haskell sub-typeclass requires UndecidableInstances?

Consider the following code example:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-} -- Is there a way to avoid this?
-- A generic class with a generic function.
class Foo a where
foo :: a -> a
-- A specific class with specific functions.
class Bar a where
bar :: a -> a
baz :: a -> a
-- Given the specific class functions, we can implement the generic class function.
instance Bar a => Foo a where
foo = bar . baz
-- So if a type belongs to the specific class...
instance Bar String where
bar = id
baz = id
-- We can invoke the generic function on it.
main :: IO ()
main =
putStrLn (foo "bar")
(My actual code is way more elaborate; this is a minimal boiled-down case to demonstrate the pattern.)
It isn't clear to me why UndecidableInstances are needed here - the type parameter a appears once in both sides of the Bar a => Foo a, so I expected things to "just work". I'm obviously missing something here. But at any rate, is there a way to do this without using UndecidableInstances?
There are a few approaches you can take; I don't think you've provided enough context to determine which would be the most appropriate. If you're using GHC-7.4, you might want to try the DefaultSignatures extension.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DefaultSignatures #-}
-- A generic class with a generic function.
class Foo a where
foo :: a -> a
default foo :: Bar a => a -> a
foo = bar . baz
-- A specific class with specific functions.
class Bar a where
bar :: a -> a
baz :: a -> a
instance Bar String where
bar = id
baz = id
instance Foo String
main :: IO ()
main =
putStrLn (foo "bar")
You still need to declare that a type is an instance of Foo, but you don't need to repeat the method declaration because the default implementation will be used.
Another fairly lightweight approach is to use a newtype. If you have functions that need a Foo instance, you can wrap a Bar instance in the newtype.
newtype FooBar a = FooBar { unFooBar :: a }
instance Bar a => Foo (FooBar a) where
foo = FooBar . bar . baz . unFooBar
-- imported from a library or something...
needsFoo :: Foo a => a -> b
myFunc = needsFoo (FooBar someBar)
Alternatively, you may be able to get by with replacing foo with a normal function, or making a specialized version for Bar instances:
-- if every `Foo` is also a `Bar`, you can just do this. No need for `Foo` at all!
foo :: Bar a => a -> a
foo = bar . baz
-- if most `Foo`s aren't `Bar`s, you may be able to use this function when you have a `Bar`
fooBar :: Bar a => a -> a
foo = bar . baz
These are probably the best solutions if they work for your situation.
Another option is to declare every Foo instance manually. Although there may be a lot of different conceivable instances, it's fairly common for codebases to only have a handful of instances that are actually used. If that's true here, it's probably less work to just write out the 3 or 4 instances you need rather than try to implement a more general solution.
As a very last resort, you can use something like your original code, but you'll also need OverlappingInstances to make it work (if you don't need OverlappingInstances, then you don't need a Foo class). This is the extension that allows GHC to choose the "most specific instance" when there are multiple available matches. This will more or less work, although you may not get what you expect.
class Foo a where
foo :: a -> a
class Bar a where
bar :: a -> a
baz :: a -> a
instance Bar String where
bar = id
baz = id
instance Bar a => Foo a where
foo = bar . baz
instance Foo [a] where
foo _ = []
main :: IO ()
main =
print (foo "foo")
Now main prints an empty string. There are two Foo instances, for a and [a]. The latter is more specific, so it gets chosen for foo "foo" since a string has type [Char], although you probably wanted the former. So now you'd also need to write
instance Foo String where
foo = bar . baz
at which point you may as well leave out the Bar a => Foo a instance entirely.
In addition to answer above. Politics used in Data.Traversable module from base library is attractive. In short, giving generic instance in library forces end user to accept your decision, and this is not always the best thing to do. Data.Traversable contains functions like foldMapDefault, which gives default implementation, but decision of specific implementation is still up to user.

Inclusion of typeclasses with default implementation in Haskell

Consider the following definitions:
class Foo a where
foo :: a -> Int
class Bar a where
bar :: a -> [Int]
Now, how do I say "every Foo is also a Bar, with bar defined by default as bar x = [foo x]" in Haskell?
(Whatever I try, the compiler gives me "Illegal instance declaration" or "Constraint is no smaller than the instance head")
Btw, I can define my Foo and Bar classes in some other way, if this would help.
class Foo a where
foo :: a -> Int
-- 'a' belongs to 'Bar' only if it belongs to 'Foo' also
class Foo a => Bar a where
bar :: a -> [Int]
bar x = [foo x] -- yes, you can specify default implementation
instance Foo Char where
foo _ = 0
-- instance with default 'bar' implementation
instance Bar Char
As the automatic definition of a Bar instance through a Foo instance can lead to undecidable cases for the compiler - i.e. one explicit instance and one through Foo conflicting with each other - , we need some special options to allow the desired behaviour. The rest through is quite straigtforward.
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
class Foo a where
foo :: a -> Int
class Bar a where
bar :: a -> [Int]
instance (Foo a) => Bar a where
bar x = [foo x]
Generally speaking you don't model things with type classes this way[*] - i.e. an instance of a type class should always be some concrete type, though that type itself can be parameteric - e.g. the Show instance for pair has this signature:
instance (Show a, Show b) => Show (a,b) where
Some of the approaches to "Generics" allow you to model a general base case and then have type specific exceptional cases. SYB3 allowed this - perhaps unfortunately SYB3 isn't the common practice Generics library it is Data.Data / Data.Generics which I think is SYB1.
[*] In the wild the story is a little more complicated - as Dario says UndecidableInstances can enable it.

Resources