Orphan instance [GHC-90177]

Flag: -Worphans
Enabled by: -Wall

When writing an instance for a typeclass, the ideal situation is that this instance is defined either in the same module as the typeclass, or in the same module as the datatype. This ensures that if a module imports either the typeclass or the datatype module, the instances will also be visible.

If the instances are defined in a separate module, it becomes possible that the typeclass and the datatype are brought into scope but the instance for that datatype is not, leading to unexpected No instance of Foo for type Bar.

Whilst this is not always avoidable, it is best practice to place the instance in the module that defines either the typeclass or the datatype. However that solution is not always possible (for example in cases where both the typeclass and the data type are declared in 3rd party libraries). In such cases we can wrap the datatype in newtype, and then define an instance of the class for the newtype in the same module.

Examples

Orphan instance in a separate module from definitions

In this example, the implementation for IsAFoo Foo is in a different module than both the definition for class IsAFoo and the datatype Foo. Thus, it would be possible for a user to write import Foo and expect to have instance IsAFoo Foo in scope; however, the user would need to additionally import module OrphanInstance.

In this case, where the definitions for both the typeclass and the type are available, the solution is to move the instance definition into the Foo module.

Error Message

OrphanInstance.hs:5:1: warning: [-Worphans] [GHC-90177]
    Orphan instance: instance IsAFoo Foo
    To avoid this
        move the instance declaration to the module of the class or of the type, or
        wrap the type with a newtype and declare the instance on the new type.
  |
5 | instance IsAFoo Foo where
  | ^^^^^^^^^^^^^^^^^^^^^^^^^...
Foo.hs
Before
module Foo where

data Foo = Foo

class IsAFoo x where
    convertToFoo :: x -> Foo
After
module Foo where

data Foo = Foo

class IsAFoo x where
    convertToFoo :: x -> Foo

instance IsAFoo Foo where
    convertToFoo = id
OrphanInstance.hs
Before
module OrphanInstance where

import Foo

instance IsAFoo Foo where
    convertToFoo = id
After
module OrphanInstance where

import Foo