[GHC] #10607: Auto derive from top to bottom
GHC
ghc-devs at haskell.org
Thu Mar 2 05:38:04 UTC 2017
#10607: Auto derive from top to bottom
-------------------------------------+-------------------------------------
Reporter: songzh | Owner: (none)
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords: deriving,
| typeclass, auto
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #13324 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by songzh):
Replying to [comment:18 RyanGlScott]:
> Alright. I've opened up #13324 to track the feature request for using
type wildcards in derived instance contexts, since that has applications
besides `derive-topdown`.
>
> Song, would this approach work for your needs?
Thanks, but I think there still is one problem.
When writing the TH code, I encountered three problems. One is the context
generation problem which you are trying to solve for me. Another is type
synonym. I want to expand it to data or newtype declaration to generate
instance, but now I forced user to use `XTypeSynonymInstances`. Richard
introduced me `th-expand-syns` which I am not quite sure how it can be
used to help on my problem now.
The last problem is the most severe one. It is about `isInstance`
function.
My process of generation standalone instances is dead simple by using type
`StateT [Type] Q [Dec]`. The roughly sketched algorithm is the following:
For a type `T`, get all its arguments of data constructors and prepare to
generate instance of class `C`. But before the generation, for each of the
argument `arg_n` we check two things:
1, whether the type `arg_n` already an instance of the class which may be
built in GHC. (by using `isInstance` function in `Langauge.Haskell.TH`)
2, whether it has already been generated. (by looking into the state hold
by the state monad)
If neither the case, we generate an standalone declaration and add the
type into the list of state monad for avoiding future duplicated
generation. After that call the instance generation function recursively.
The above two cases are the base cases for the recursion.
The problem is: For case 1, we cannot check a type such as `[a]`, `(a,b)`
is an instance of Eq or Ord with `isInstance` function, no matter we give
the type class context or not:
{{{
{-# LANGUAGE TemplateHaskell,QuasiQuotes,ExplicitForAll #-}
import Language.Haskell.TH
char :: Q Bool
char = do
char_t <- [t| Char |]
isInstance ''Eq [char_t]
> $(char >>= stringE.show)
"True
poly_a :: Q Bool
poly_a = do
poly_a_t <- [t| forall a. Eq a => [a] |]
isInstance ''Eq [poly_a_t]
> $(poly_a >>= stringE.show)
"False"
poly_a' :: Q Bool
poly_a' = do
poly_a_t <- [t| forall a. [a] |]
isInstance ''Eq [poly_a_t]
-- False
pair :: Q Bool
pair = do
pair_t <- [t| forall a b. (a,b) |]
isInstance ''Eq [pair_t]
-- False
pair' :: Q Bool
pair' = do
pair_t <- [t| forall a b. (Eq a, Eq b) => (a,b) |]
isInstance ''Eq [pair_t]
-- False
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10607#comment:19>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list