Skip to content

GitLab

  • Menu
Projects Groups Snippets
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
  • GHC GHC
  • Project information
    • Project information
    • Activity
    • Labels
    • Members
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,867
    • Issues 4,867
    • List
    • Boards
    • Service Desk
    • Milestones
    • Iterations
  • Merge requests 457
    • Merge requests 457
  • CI/CD
    • CI/CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Deployments
    • Deployments
    • Releases
  • Analytics
    • Analytics
    • Value stream
    • CI/CD
    • Code review
    • Insights
    • Issue
    • Repository
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #19549
Closed
Open
Created Mar 16, 2021 by Icelandjack@IcelandjackReporter

"Mismatch in type between binder and occurrence"

{-# Options_GHC -O2 -fstatic-argument-transformation -dcore-lint -fobject-code #-}

replace2_4 :: [a] -> a -> a -> [a]
replace2_4 = go 0 where

 go :: Int -> [a] -> a -> a -> [a]
 go 2 (a:as) two four =  two:go 3 as two four
 go 4 (a:as) two four = four:as
 go n (a:as) two four = a:go (1+n) as two four

The problem seems to persist if I add forall a. or replace four:as with four:go 5 as two four. This is the error I get:

GHCi, version 8.10.0.20191123: https://www.haskell.org/ghc/  :? for help
[1 of 1] Compiling Main             ( /home/baldur/hs/4203.hs, /home/baldur/hs/4203.o )
*** Core Lint errors : in result of Static argument ***
/home/baldur/hs/4203.hs:7:18: warning:
    Mismatch in type between binder and occurrence
    Var: go_s1pB
    Binder type: forall a a.
                 Int -> [a_aCh] -> a_aCh -> a_aCh -> [a_aCh]
    Occurrence type: forall a a. Int -> [a] -> a -> a -> [a]
      Before subst: forall a a. Int -> [a] -> a -> a -> [a]
    In the RHS of go_s1pB :: forall a a. Int -> [a] -> a -> a -> [a]
    In the body of lambda with binder a_aC0 :: *
    In the body of lambda with binder a_aCh :: *
    In the body of lambda with binder ds_d1o5 :: Int
    In the body of lambda with binder ds_d1o6 :: [a_aCh]
    In the body of lambda with binder two_aAY :: a_aCh
    In the body of lambda with binder four_aAZ :: a_aCh
    In the RHS of sat_worker_s1pT :: Int -> [a_aCh] -> [a_aCh]
    In the body of lambda with binder ds_d1o5 :: Int
    In the body of lambda with binder ds_d1o6 :: [a_aCh]
    In the body of letrec with binders go_s1pB :: forall a a.
                                                  Int -> [a_aCh] -> a_aCh -> a_aCh -> [a_aCh]
    In the RHS of fail_d1pg :: Void# -> [a_aCh]
    In the body of lambda with binder ds_d1ph :: Void#
    In a case alternative: (: a_aB5 :: a_aCh, as_aB6 :: [a_aCh])
    Substitution: [TCvSubst
                     In scope: InScope {wild_Xc two_aAY four_aAZ a_aB5 as_aB6 a_aC0
                                        a_aCh ds_d1o5 ds_d1o6 ds_d1ph replace2_4 $trModule go_s1pB
                                        replace2_4_s1pC $trModule_s1pD $trModule_s1pE $trModule_s1pF
                                        $trModule_s1pG sat_worker_s1pT}
                     Type env: []
                     Co env: []]
*** Offending Program ***
go_s1pB [Occ=LoopBreaker]
  :: forall a a. Int -> [a] -> a -> a -> [a]
[LclId,
 Arity=4,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [40 179 0 0] 423 60}]
go_s1pB
  = \ (@ a_aC0)
      (@ a_aCh)
      (ds_d1o5 :: Int)
      (ds_d1o6 :: [a_aCh])
      (two_aAY :: a_aCh)
      (four_aAZ :: a_aCh) ->
      letrec {
        sat_worker_s1pT :: Int -> [a_aCh] -> [a_aCh]
        [LclId]
        sat_worker_s1pT
          = \ (ds_d1o5 :: Int) (ds_d1o6 :: [a_aCh]) ->
              let {
                go_s1pB :: forall a a. Int -> [a_aCh] -> a_aCh -> a_aCh -> [a_aCh]
                [LclId]
                go_s1pB
                  = \ (@ a_s1pP)
                      (@ a_s1pQ)
                      (ds_d1o5 :: Int)
                      (ds_d1o6 :: [a_aCh])
                      (two_s1pR :: a_aCh)
                      (four_s1pS :: a_aCh) ->
                      sat_worker_s1pT ds_d1o5 ds_d1o6 } in
              join {
                fail_d1pg :: Void# -> [a_aCh]
                [LclId[JoinId(1)],
                 Arity=1,
                 Str=<L,U>,
                 Unf=Unf{Src=<vanilla>, TopLvl=False, Value=True, ConLike=True,
                         WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 251 30}]
                fail_d1pg _ [Occ=Dead, OS=OneShot]
                  = case ds_d1o6 of {
                      [] ->
                        patError
                          @ 'LiftedRep
                          @ [a_aCh]
                          "/home/baldur/hs/4203.hs:(7,2)-(9,46)|function go"#;
                      : a_aB5 as_aB6 ->
                        : @ a_aCh
                          a_aB5
                          (go_s1pB
                             @ a_aC0
                             @ a_aCh
                             (case ds_d1o5 of { I# y_a1pr -> I# (+# 1# y_a1pr) })
                             as_aB6
                             two_aAY
                             four_aAZ)
                    } } in
              case ds_d1o5 of { I# ds_d1pd ->
              case ds_d1pd of {
                __DEFAULT -> jump fail_d1pg void#;
                2# ->
                  case ds_d1o6 of {
                    [] -> jump fail_d1pg void#;
                    : a_aAW as_aAX ->
                      : @ a_aCh
                        two_aAY
                        (go_s1pB @ a_aC0 @ a_aCh (I# 3#) as_aAX two_aAY four_aAZ)
                  };
                4# ->
                  case ds_d1o6 of {
                    [] -> jump fail_d1pg void#;
                    : a_aB0 as_aB1 -> : @ a_aCh four_aAZ as_aB1
                  }
              }
              }; } in
      sat_worker_s1pT ds_d1o5 ds_d1o6

replace2_4_s1pC :: Int
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
replace2_4_s1pC = I# 0#

replace2_4 :: forall a. [a] -> a -> a -> [a]
[LclIdX,
 Arity=3,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 60}]
replace2_4 = \ (@ a_aC0) -> go_s1pB @ a_aC0 @ a_aC0 replace2_4_s1pC

$trModule_s1pD :: Addr#
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
$trModule_s1pD = "main"#

$trModule_s1pE :: TrName
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
$trModule_s1pE = TrNameS $trModule_s1pD

$trModule_s1pF :: Addr#
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
$trModule_s1pF = "Main"#

$trModule_s1pG :: TrName
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
$trModule_s1pG = TrNameS $trModule_s1pF

$trModule :: Module
[LclIdX,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
$trModule = Module $trModule_s1pE $trModule_s1pG

*** End of Offense ***


<no location info>: error:
Compilation had errors


*** Exception: ExitFailure 1
>
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Assignee
Assign to
Time tracking