[GHC] #9429: Alternative to type family Any
GHC
ghc-devs at haskell.org
Fri Nov 3 18:58:14 UTC 2017
#9429: Alternative to type family Any
-------------------------------------+-------------------------------------
Reporter: mboes | Owner: (none)
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords: TypeFamilies
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: 9097, 9380 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Apologies for reviving a long-dormant thread, but my understand is now
that #12369 has been fixed, there is a way to achieve something like the
`Any` of yore—just use a data family with a polymorphic return kind. That
is:
{{{#!hs
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
data family Any :: k
}}}
Since `Any` is a data family, it has a `Typeable` instance:
{{{#!hs
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
import Type.Reflection
data family Any :: k
main :: IO ()
main = print $ typeRep @(Any :: *)
}}}
{{{
$ ~/Software/ghc/inplace/bin/runghc Foo.hs
Any *
}}}
Moreover, it inhabits every kind and is a distinguishable element, so you
can write things like this:
{{{#!hs
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
import GHC.TypeLits
import Type.Reflection
data family Any :: k
type family Foo (a :: Bool) :: Symbol where
Foo False = "It's false"
Foo Any = "It's Any"
Foo True = "It's true"
main :: IO ()
main = do
print $ typeRep @(Foo False)
print $ typeRep @(Foo Any)
print $ typeRep @(Foo True)
}}}
{{{
$ ~/Software/ghc/inplace/bin/runghc Foo2.hs
"It's false"
"It's Any"
"It's true"
}}}
Does this work for your use cases?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9429#comment:31>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list