Skip to content

Instantly share code, notes, and snippets.

@awalterschulze
Last active May 4, 2023 01:13
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save awalterschulze/4664dcc7b9299bda6f9131663dd54736 to your computer and use it in GitHub Desktop.
Save awalterschulze/4664dcc7b9299bda6f9131663dd54736 to your computer and use it in GitHub Desktop.
Problems with GADT and deriving

GADT and deriving

I have recently started playing around with GADTs, but I am struggling to get it to play along with deriving.

In this gist I have included all files necessary to reproduce the problems in a single stackage package. Simply clone and run make. The libraries giving the problems are commented out in the cabal file.
By uncommenting a library you can reproduce the respective build errors.

I started by following this explanation of GADTs https://en.wikibooks.org/wiki/Haskell/GADT

In there we get the following example of expressions:

{-#LANGUAGE GADTs #-}

data Expr a where
    I   :: Int  -> Expr Int
    B   :: Bool -> Expr Bool
    Add :: Expr Int -> Expr Int -> Expr Int
    Mul :: Expr Int -> Expr Int -> Expr Int
    Eq  :: Expr Int -> Expr Int -> Expr Bool

In Working.hs I added the following deriving instances and it worked:

{-#LANGUAGE GADTs, StandaloneDeriving #-}

deriving instance Eq a => Eq (Expr a)
deriving instance Show a => Show (Expr a)

Next in AddOrd.hs I added the Ord deriving instance:

deriving instance Ord a => Ord (Expr a)

And it gave the following error:

/Users/waschulze/Desktop/4664dcc7b9299bda6f9131663dd54736/AddOrd.hs:15:1: error:
    • Couldn't match type ‘Bool’ with ‘Int’
      Inaccessible code in
        a pattern with constructor: I :: Int -> Expr Int,
        in a case alternative
    • In the pattern: I {}
      In a case alternative: I {} -> GT
      In the expression:
        case b of {
          I {} -> GT
          B b1 -> (a1 `compare` b1)
          _ -> LT }
      When typechecking the code for ‘compare’
        in a derived instance for ‘Ord (Expr a)’:
        To see the code I am typechecking, use -ddump-deriv

/Users/waschulze/Desktop/4664dcc7b9299bda6f9131663dd54736/AddOrd.hs:15:1: error:
    • Couldn't match type ‘Int’ with ‘Bool’
      Inaccessible code in
        a pattern with constructor:
          Eq :: Expr Int -> Expr Int -> Expr Bool,
        in a case alternative
    • In the pattern: Eq {}
      In a case alternative: Eq {} -> LT
      In the expression:
        case b of {
          Eq {} -> LT
          Mul b1 b2
            -> case (compare a1 b1) of {
                 LT -> LT
                 EQ -> (a2 `compare` b2)
                 GT -> GT }
          _ -> GT }
      When typechecking the code for ‘compare’
        in a derived instance for ‘Ord (Expr a)’:
        To see the code I am typechecking, use -ddump-deriv

I fixed this, in Swapped.hs, simply swapping some constructors around:

data Expr a where
    Eq  :: Expr Int -> Expr Int -> Expr Bool
    B   :: Bool -> Expr Bool
    I   :: Int  -> Expr Int
    Add :: Expr Int -> Expr Int -> Expr Int
    Mul :: Expr Int -> Expr Int -> Expr Int

I wonder why this would make a difference?

Next, in Constant.hs, I added a single constant constructor for all types:

data Expr a where
    Eq  :: Expr Int -> Expr Int -> Expr Bool
    Const   :: a -> Expr a
    Add :: Expr Int -> Expr Int -> Expr Int
    Mul :: Expr Int -> Expr Int -> Expr Int

This still worked.

Then, in General.hs, I generalised the Eq expression:

data Expr a where
    Eq  :: Expr a -> Expr a -> Expr Bool
    Const   :: a -> Expr a
    Add :: Expr Int -> Expr Int -> Expr Int
    Mul :: Expr Int -> Expr Int -> Expr Int

And again I got an error:

/Users/waschulze/Desktop/4664dcc7b9299bda6f9131663dd54736/General.hs:13:1: error:
    • Could not deduce: a2 ~ a1
      from the context: a ~ Bool
        bound by a pattern with constructor:
                   Eq :: forall a. Expr a -> Expr a -> Expr Bool,
                 in an equation for ‘==’
        at General.hs:13:1-37
      ‘a2’ is a rigid type variable bound by
        a pattern with constructor:
          Eq :: forall a. Expr a -> Expr a -> Expr Bool,
        in an equation for ‘==’
        at General.hs:13:1
      ‘a1’ is a rigid type variable bound by
        a pattern with constructor:
          Eq :: forall a. Expr a -> Expr a -> Expr Bool,
        in an equation for ‘==’
        at General.hs:13:1
      Expected type: Expr a1
        Actual type: Expr a2
    • In the second argument of ‘(==)’, namely ‘b1’
      In the first argument of ‘(&&)’, namely ‘((a1 == b1))’
      In the expression: (((a1 == b1)) && ((a2 == b2)))
      When typechecking the code for ‘==’
        in a derived instance for ‘Eq (Expr a)’:
        To see the code I am typechecking, use -ddump-deriv
    • Relevant bindings include
        b2 :: Expr a2 (bound at General.hs:13:1)
        b1 :: Expr a2 (bound at General.hs:13:1)
        a2 :: Expr a1 (bound at General.hs:13:1)
        a1 :: Expr a1 (bound at General.hs:13:1)

/Users/waschulze/Desktop/4664dcc7b9299bda6f9131663dd54736/General.hs:14:1: error:
    • Could not deduce: a2 ~ a1
      from the context: a ~ Bool
        bound by a pattern with constructor:
                   Eq :: forall a. Expr a -> Expr a -> Expr Bool,
                 in a case alternative
        at General.hs:14:1-39
      ‘a2’ is a rigid type variable bound by
        a pattern with constructor:
          Eq :: forall a. Expr a -> Expr a -> Expr Bool,
        in a case alternative
        at General.hs:14:1
      ‘a1’ is a rigid type variable bound by
        a pattern with constructor:
          Eq :: forall a. Expr a -> Expr a -> Expr Bool,
        in a case alternative
        at General.hs:14:1
      Expected type: Expr a1
        Actual type: Expr a2
    • In the second argument of ‘compare’, namely ‘b1’
      In the expression: (compare a1 b1)
      In the expression:
        case (compare a1 b1) of {
          LT -> LT
          EQ -> (a2 `compare` b2)
          GT -> GT }
      When typechecking the code for ‘compare’
        in a derived instance for ‘Ord (Expr a)’:
        To see the code I am typechecking, use -ddump-deriv
    • Relevant bindings include
        b2 :: Expr a2 (bound at General.hs:14:1)
        b1 :: Expr a2 (bound at General.hs:14:1)
        a2 :: Expr a1 (bound at General.hs:14:1)
        a1 :: Expr a1 (bound at General.hs:14:1)

/Users/waschulze/Desktop/4664dcc7b9299bda6f9131663dd54736/General.hs:15:1: error:
    • Could not deduce (Show a1) arising from a use of ‘showsPrec’
      from the context: Show a
        bound by the instance declaration at General.hs:15:1-41
      or from: a ~ Bool
        bound by a pattern with constructor:
                   Eq :: forall a. Expr a -> Expr a -> Expr Bool,
                 in an equation for ‘showsPrec’
        at General.hs:15:1-41
      Possible fix:
        add (Show a1) to the context of the data constructor ‘Eq’
    • In the first argument of ‘(.)’, namely ‘(showsPrec 11 b1)’
      In the second argument of ‘(.)’, namely
        ‘(.) (showsPrec 11 b1) ((.) GHC.Show.showSpace (showsPrec 11 b2))’
      In the second argument of ‘showParen’, namely
        ‘((.)
            (showString "Eq ")
            ((.)
               (showsPrec 11 b1) ((.) GHC.Show.showSpace (showsPrec 11 b2))))’
      When typechecking the code for ‘showsPrec’
        in a derived instance for ‘Show (Expr a)’:
        To see the code I am typechecking, use -ddump-deriv

Trying to simplify and swapped the constructors around does not help anymore:

data Expr a where
    Eq  :: Expr a -> Expr a -> Expr Bool
    B   :: Bool -> Expr Bool

This also produces a large error.

I would like to apply GADTs to a much larger set of expressions where I find it crucial to derive Eq and Ord. So if I can't get these simple examples to work I will have to stick to plain ADTs. I would appreciate any advice on things I could try, but I hope that I am just doing something wrong?

{-#LANGUAGE GADTs, StandaloneDeriving #-}
module AddOrd
( someFunc
) where
data Expr a where
I :: Int -> Expr Int
B :: Bool -> Expr Bool
Add :: Expr Int -> Expr Int -> Expr Int
Mul :: Expr Int -> Expr Int -> Expr Int
Eq :: Expr Int -> Expr Int -> Expr Bool
deriving instance Eq a => Eq (Expr a)
deriving instance Ord a => Ord (Expr a)
deriving instance Show a => Show (Expr a)
someFunc :: IO ()
someFunc = print $ Eq (I 5) (I 5)
{-#LANGUAGE GADTs, StandaloneDeriving #-}
module Constant
( someFunc
) where
data Expr a where
Eq :: Expr Int -> Expr Int -> Expr Bool
Const :: a -> Expr a
Add :: Expr Int -> Expr Int -> Expr Int
Mul :: Expr Int -> Expr Int -> Expr Int
deriving instance Eq a => Eq (Expr a)
deriving instance Ord a => Ord (Expr a)
deriving instance Show a => Show (Expr a)
someFunc :: IO ()
someFunc = print $ Eq (Const 6) (Const 5)
name: derivinggadt
version: 0.1.0.0
-- synopsis:
-- description:
homepage: https://github.com/awalterschulze/derivinggadt#readme
license: BSD3
license-file: LICENSE
author: Walter Schulze
maintainer: awalterschulze@gmail.com
copyright: Walter Schulze
category: Web
build-type: Simple
extra-source-files: README.md
cabal-version: >=1.10
library
hs-source-dirs: .
exposed-modules: Working
-- , AddOrd
, Swapped
, Constant
-- , General
build-depends: base >= 4.7 && < 5
default-language: Haskell2010
executable derivinggadt-exe
hs-source-dirs: .
main-is: Main.hs
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends: base
, derivinggadt
default-language: Haskell2010
source-repository head
type: git
location: https://gist.github.com/awalterschulze/4664dcc7b9299bda6f9131663dd54736
{-#LANGUAGE GADTs, StandaloneDeriving #-}
module General
( someFunc
) where
data Expr a where
Eq :: Expr a -> Expr a -> Expr Bool
Const :: a -> Expr a
Add :: Expr Int -> Expr Int -> Expr Int
Mul :: Expr Int -> Expr Int -> Expr Int
deriving instance Eq a => Eq (Expr a)
deriving instance Ord a => Ord (Expr a)
deriving instance Show a => Show (Expr a)
someFunc :: IO ()
someFunc = print $ Eq (Const 6) (Const 5)
Copyright Walter Schulze (c) 2017
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:
* Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
* Redistributions in binary form must reproduce the above
copyright notice, this list of conditions and the following
disclaimer in the documentation and/or other materials provided
with the distribution.
* Neither the name of Walter Schulze nor the names of other
contributors may be used to endorse or promote products derived
from this software without specific prior written permission.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
module Main where
import Working
main :: IO ()
main = someFunc
build:
stack build --ghc-options " -ddump-deriv"
run: build
stack exec derivinggadt-exe
import Distribution.Simple
main = defaultMain
# This file was automatically generated by 'stack init'
#
# Some commonly used options have been documented as comments in this file.
# For advanced use and comprehensive documentation of the format, please see:
# http://docs.haskellstack.org/en/stable/yaml_configuration/
# Resolver to choose a 'specific' stackage snapshot or a compiler version.
# A snapshot resolver dictates the compiler version and the set of packages
# to be used for project dependencies. For example:
#
# resolver: lts-3.5
# resolver: nightly-2015-09-21
# resolver: ghc-7.10.2
# resolver: ghcjs-0.1.0_ghc-7.10.2
# resolver:
# name: custom-snapshot
# location: "./custom-snapshot.yaml"
resolver: lts-9.11
# User packages to be built.
# Various formats can be used as shown in the example below.
#
# packages:
# - some-directory
# - https://example.com/foo/bar/baz-0.0.2.tar.gz
# - location:
# git: https://github.com/commercialhaskell/stack.git
# commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a
# - location: https://github.com/commercialhaskell/stack/commit/e7b331f14bcffb8367cd58fbfc8b40ec7642100a
# extra-dep: true
# subdirs:
# - auto-update
# - wai
#
# A package marked 'extra-dep: true' will only be built if demanded by a
# non-dependency (i.e. a user package), and its test suites and benchmarks
# will not be run. This is useful for tweaking upstream packages.
packages:
- '.'
# Dependency packages to be pulled from upstream that are not in the resolver
# (e.g., acme-missiles-0.3)
extra-deps: []
# Override default flag values for local packages and extra-deps
flags: {}
# Extra package databases containing global packages
extra-package-dbs: []
# Control whether we use the GHC we find on the path
# system-ghc: true
#
# Require a specific version of stack, using version ranges
# require-stack-version: -any # Default
# require-stack-version: ">=1.3"
#
# Override the architecture used by stack, especially useful on Windows
# arch: i386
# arch: x86_64
#
# Extra directories used by stack for building
# extra-include-dirs: [/path/to/dir]
# extra-lib-dirs: [/path/to/dir]
#
# Allow a newer minor version of GHC than the snapshot specifies
# compiler-check: newer-minor
{-#LANGUAGE GADTs, StandaloneDeriving #-}
module Swapped
( someFunc
) where
data Expr a where
Eq :: Expr Int -> Expr Int -> Expr Bool
B :: Bool -> Expr Bool
I :: Int -> Expr Int
Add :: Expr Int -> Expr Int -> Expr Int
Mul :: Expr Int -> Expr Int -> Expr Int
deriving instance Eq a => Eq (Expr a)
deriving instance Ord a => Ord (Expr a)
deriving instance Show a => Show (Expr a)
someFunc :: IO ()
someFunc = print $ Eq (I 6) (I 5)
{-#LANGUAGE GADTs, StandaloneDeriving #-}
module Working
( someFunc
) where
data Expr a where
I :: Int -> Expr Int
B :: Bool -> Expr Bool
Add :: Expr Int -> Expr Int -> Expr Int
Mul :: Expr Int -> Expr Int -> Expr Int
Eq :: Expr Int -> Expr Int -> Expr Bool
deriving instance Eq a => Eq (Expr a)
deriving instance Show a => Show (Expr a)
someFunc :: IO ()
someFunc = print $ Eq (I 6) (I 5)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment