<div>Hi<br></div><div><br></div><div>I have a project built around servant + persistent(-postgresql) + esqueleto (and many other libraries).<br></div><div>I recently upgraded it to newer versions of GHC and my dependencies and I'm running into a problem which I don't fully understand.<br></div><div><br></div><div>```<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘==’<br></div><div>          from type ‘ghc-prim-0.5.3:GHC.Prim.Int#<br></div><div>                     -> ghc-prim-0.5.3:GHC.Prim.Int# -> Bool’<br></div><div>            to type ‘Key ActivationCode -> Key ActivationCode -> Bool’<br></div><div>    • When deriving the instance for (Eq (Key ActivationCode))<br></div><div><br></div><div>+ other similar<br></div><div>```<br></div><div>(full trace + Model.hs below)</div><div><br></div><div>I get these errors on all my model entities.<br></div><div>First of all I don't really understand the error message and I don't understand why I am getting it. I am using these entities (and their key) in esqueleto database operations:<br></div><div><br></div><div>```<br></div><div>findActivationCodeById :: ActivationCodeId -> IO (Entity ActivationCode)<br></div><div>```<br></div><div><br></div><div>I don't get the error if I build with `stack build --fast` (at least the Model.hs builds).<br></div><div>I've tried to reproduce this on a smaller project with nothing but this Model file however it compiles there.<br></div><div>Additionally even if I remove the `deriving Eq` it doesn't change the error (it's still deriving Eq, Ord, ..).<br></div><div><br></div><div>Could anyone give me some hints where I should start looking? Is it due to a language extension?<br></div><div><br></div><div>In my (generated) cabal<br></div><div><br></div><div>```<br></div><div>  default-extensions: TypeOperators OverloadedStrings DeriveGeneric RecordWildCards DuplicateRecordFields StrictData<br></div><div>```<br></div><div><br></div><div>Thanks!</div><div><br></div><div>Model.hs (trimmed down to just one entity)<br></div><div><br></div><div>{-# LANGUAGE EmptyDataDecls             #-}<br></div><div>{-# LANGUAGE FlexibleContexts           #-}<br></div><div>{-# LANGUAGE GADTs                      #-}<br></div><div>{-# LANGUAGE GeneralizedNewtypeDeriving #-}<br></div><div>{-# LANGUAGE MultiParamTypeClasses      #-}<br></div><div>{-# LANGUAGE OverloadedStrings          #-}<br></div><div>{-# LANGUAGE QuasiQuotes                #-}<br></div><div>{-# LANGUAGE TemplateHaskell            #-}<br></div><div>{-# LANGUAGE TypeFamilies               #-}<br></div><div>{-# LANGUAGE FlexibleInstances          #-} -- allow json in data model<br></div><div><br></div><div>module Prolix.Model.Model where<br></div><div><br></div><div>import qualified Data.Aeson as Aeson<br></div><div>import qualified Data.Fixed as Fixed<br></div><div>import           Data.Text (Text)<br></div><div>import           Data.Time<br></div><div>import           Data.Typeable (Typeable)<br></div><div>import           Database.Persist.Postgresql<br></div><div>import           Database.Persist.TH<br></div><div><br></div><div>import           GHC.Generics<br></div><div><br></div><div>share [ mkPersist sqlSettings<br></div><div>      , mkDeleteCascade sqlSettings<br></div><div>      , mkMigrate "migrateAll"<br></div><div>      ] [persistLowerCase|<br></div><div><br></div><div>ActivationCode json<br></div><div>    productCode Int           sql=accd_product_code<br></div><div>    code Text                 sql=accd_code<br></div><div>    provider Text             sql=accd_provider<br></div><div>    exported Bool             sql=accd_exported<br></div><div>    exportedOn UTCTime Maybe  sql=accd_exported_on<br></div><div>    createdOn UTCTime         sql=accd_created_on default=now()<br></div><div>    modifiedOn UTCTime        sql=accd_modified_on default=now()<br></div><div>    UniqueActivationCode code provider<br></div><div>    deriving Eq Ord Show Generic<br></div><div>|]<br></div><div><br></div><div><br></div><div>Full trace<br></div><div><br></div><div>[ 54 of 155] Compiling Prolix.Model.Model ( src/Prolix/Model/Model.hs, .stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/Prolix/Model/Model.o ) [Optimisation flags changed]<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘==’<br></div><div>          from type ‘ghc-prim-0.5.3:GHC.Prim.Int#<br></div><div>                     -> ghc-prim-0.5.3:GHC.Prim.Int# -> Bool’<br></div><div>            to type ‘Key ActivationCode -> Key ActivationCode -> Bool’<br></div><div>    • When deriving the instance for (Eq (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘compare’<br></div><div>          from type ‘ghc-prim-0.5.3:GHC.Prim.Int#<br></div><div>                     -> ghc-prim-0.5.3:GHC.Prim.Int# -> Ordering’<br></div><div>            to type ‘Key ActivationCode -> Key ActivationCode -> Ordering’<br></div><div>    • When deriving the instance for (Ord (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘path-pieces-0.2.1:Web.PathPieces.toPathPiece’<br></div><div>          from type ‘ghc-prim-0.5.3:GHC.Prim.Int# -> Text’<br></div><div>            to type ‘Key ActivationCode -> Text’<br></div><div>    • When deriving the instance for (path-pieces-0.2.1:Web.PathPieces.PathPiece<br></div><div>                                        (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘Web.Internal.HttpApiData.toUrlPiece’<br></div><div>          from type ‘ghc-prim-0.5.3:GHC.Prim.Int# -> Text’<br></div><div>            to type ‘Key ActivationCode -> Text’<br></div><div>    • When deriving the instance for (Web.Internal.HttpApiData.ToHttpApiData<br></div><div>                                        (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • No instance for (Web.Internal.HttpApiData.FromHttpApiData<br></div><div>                         ghc-prim-0.5.3:GHC.Prim.Int#)<br></div><div>        arising from the 'deriving' clause of a data type declaration<br></div><div>      Possible fix:<br></div><div>        use a standalone 'deriving instance' declaration,<br></div><div>          so you can specify the instance context yourself<br></div><div>    • When deriving the instance for (Web.Internal.HttpApiData.FromHttpApiData<br></div><div>                                        (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘toPersistValue’<br></div><div>          from type ‘ghc-prim-0.5.3:GHC.Prim.Int# -> PersistValue’<br></div><div>            to type ‘Key ActivationCode -> PersistValue’<br></div><div>    • When deriving the instance for (PersistField<br></div><div>                                        (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘sqlType’<br></div><div>          from type ‘Data.Proxy.Proxy ghc-prim-0.5.3:GHC.Prim.Int#<br></div><div>                     -> SqlType’<br></div><div>            to type ‘Data.Proxy.Proxy (Key ActivationCode) -> SqlType’<br></div><div>    • When deriving the instance for (PersistFieldSql<br></div><div>                                        (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • Couldn't match a lifted type with an unlifted type<br></div><div>        arising from the coercion of the method ‘Aeson.toJSON’<br></div><div>          from type ‘ghc-prim-0.5.3:GHC.Prim.Int# -> Aeson.Value’<br></div><div>            to type ‘Key ActivationCode -> Aeson.Value’<br></div><div>    • When deriving the instance for (Aeson.ToJSON<br></div><div>                                        (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div><div>/src/hadruki/prolix/src/Prolix/Model/Model.hs:35:1: error:<br></div><div>    • No instance for (Aeson.FromJSON ghc-prim-0.5.3:GHC.Prim.Int#)<br></div><div>        arising from the 'deriving' clause of a data type declaration<br></div><div>      Possible fix:<br></div><div>        use a standalone 'deriving instance' declaration,<br></div><div>          so you can specify the instance context yourself<br></div><div>    • When deriving the instance for (Aeson.FromJSON<br></div><div>                                        (Key ActivationCode))<br></div><div>   |<br></div><div>35 | share [ mkPersist sqlSettings<br></div><div>   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...<br></div><div><br></div>