[GHC] #16373: Strings from symbolVal not simplified at compile time

GHC ghc-devs at haskell.org
Thu Feb 28 23:39:34 UTC 2019


#16373: Strings from symbolVal not simplified at compile time
-------------------------------------+-------------------------------------
           Reporter:  roland         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.3
  (CodeGen)                          |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Compiling
 {{{#!hs
 {-# LANGUAGE DataKinds, TypeApplications #-}

 module Test where

 import GHC.TypeLits
 import Data.Proxy

 testAA :: Bool
 testAA = symbolVal @"A" Proxy == symbolVal @"A" Proxy

 testAB :: Bool
 testAB = symbolVal @"A" Proxy == symbolVal @"B" Proxy

 testAB' :: Bool
 testAB' = symbolVal @"A" Proxy == symbolVal @"B" Proxy
 }}}
 with
 {{{
 ghc -O -ddump-simpl -dsuppress-all Test.hs
 }}}
 yields:
 {{{
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 testAB'2
 testAB'2 = "B"#

 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 testAB'1
 testAB'1 = unpackCString# testAB'2

 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 testAA2
 testAA2 = "A"#

 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 testAA1
 testAA1 = unpackCString# testAA2

 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 testAB'
 testAB' = eqString testAA1 testAB'1

 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 testAB
 testAB = testAB'

 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 testAA
 testAA = eqString testAA1 testAA1
 }}}

 Furthermore, removing the type signatures for ''either'' testAB or testAB'
 makes ''both'' simplify to False!

 I would expect all three definitions to simplify to True or False,
 independently of the presence of type signatures.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16373>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list