[GHC] #14217: Interface-file decls for large tuples
GHC
ghc-devs at haskell.org
Tue Sep 12 15:11:10 UTC 2017
#14217: Interface-file decls for large tuples
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by crockeea):
Here's the code in question.
{{{
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-partial-type-signatures #-}
module Crypto.Lol.Applications.Tests.SHETests (tunnelTests) where
import Control.Monad.Random
import Crypto.Lol
import Crypto.Lol.Applications.SymmSHE
import Crypto.Lol.Tests
import qualified Test.Framework as TF
tunnelTests :: forall t r r' s s' zp zq gad . (_)
=> Proxy '(r,r',s,s',zp,zq) -> Proxy gad -> Proxy t -> TF.Test
tunnelTests _ _ _ =
let ptmr = Proxy::Proxy '(t,r,r',s,s',zp,zq,gad)
in TF.testGroup (showType ptmr)
[genTestArgs "Tunnel" prop_ringTunnel ptmr]
prop_ringTunnel ::
(TunnelHintCtx t e r s e' r' s' z zp zq gad,
EncryptCtx t r r' z zp zq,
DecryptUCtx t s s' z zp zq,
e ~ FGCD r s)
=> PT (Cyc t r zp) -> SK (Cyc t r' z) -> SK (Cyc t s' z) -> Test
'(t,r,r',s,s',zp,zq,gad)
prop_ringTunnel x skin skout = undefined
}}}
bgamari: That's useful to know! The constraints on `prop_ringTunnel`
(`TunnelHintCtx`, `EncryptCtx`, and `DecryptCtx`) are all (large)
constraint synonyms. The offending line is actually `tunnelTests _ _ _ =`.
Although the error in this ticket is killing compilation before I get a
warning about the partial type signature (which would include the entire
constraint list for `tunnelTests`), I know that the list is heinous --
that's why I'm using PTSs in the first place! It wouldn't surprise me at
all to know it had 64 items in it.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14217#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list