[Haskell-cafe] Data constructor ‘Minus’ comes from an un-promotable type ‘Ints’

Rune K. Svendsen runesvend at gmail.com
Thu Sep 15 11:51:31 UTC 2016


On Monday, May 18, 2015 at 3:23:52 PM UTC+2, Richard Eisenberg wrote:
>
>
> On May 18, 2015, at 9:06 AM, "Nicholls, Mark" <nichol... at vimn.com 
> <javascript:>> wrote:
>
> Hmmmm…
>  
> OK,
>  
> Any idea of a timescale
>
>
> In ways that would be hard to predict, promoting all types is a fairly 
> massive change to GHC. If I merge in August, I'll be quite pleased. But it 
> really should be there by 7.12, which should occur by Feb/Mar '16.
>

On Monday, May 18, 2015 at 3:23:52 PM UTC+2, Richard Eisenberg wrote:
> On May 18, 2015, at 9:06 AM, "Nicholls, Mark" <nichol... at vimn.com> wrote:
>
> Hmmmm…
>  
> OK,
>  
> Any idea of a timescale
>
>
> In ways that would be hard to predict, promoting all types is a fairly 
> massive change to GHC. If I merge in August, I'll be quite pleased. But it 
> really should be there by 7.12, which should occur by Feb/Mar '16.
>
>
I'd love to hear the status on this. I found this email thread, through a 
Google search, because I'm experiencing the same error.

I have these tagged types that I want to make part of a 
Servant.Server.Internal.Context map, which is a type-level map, that 
automagically pulls out the right type to supply whatever is needed. As a 
mere programmer, this is fairly awesome to me, but I can't get it to work 
because of the aforementioned error. Here's the code:

    {-# LANGUAGE DataKinds, TypeOperators #-}
    import qualified Data.Tagged as Tag
    import           Servant.Server.Internal.Context (Context(EmptyContext, 
(:.)))

    type BtcConf        = Tag.Tagged "BTCConf" Word
    type SettlePeriod   = Tag.Tagged "Hours" Word
    type DustLimit      = Tag.Tagged "Dust" BitcoinAmount
    type ChanConf2 = BtcConf :. BitcoinAmount :. DustLimit :. Hours :. 
EmptyContext
    -- ERROR:
    -- Data constructor ':.' comes from an un-promotable type 'Context'


            /Rune

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160915/b65b7fff/attachment.html>


More information about the Haskell-Cafe mailing list