Skip to content

GHCi segfaults with linear types imported from other module

Summary

Using ghc to evaluate a function that uses linear types and imports linearly-typed helper from another module leads to segmentation fault. Moving helper over to current module removes the problem.

After messing with cabal repl -v3 and extracting ghc command I got following stack trace in gdb (this one is for bigger project though but I believe the underlying issue is the same)

Thread 13 "ghc_worker" received signal SIGSEGV, Segmentation fault.
[Switching to Thread 0x7fffc902f6c0 (LWP 1182129)]
0x00007fffef193a38 in interpretBCO ()
   from /nix/store/8lkbri2blncc4vh4rjqfc47jdx3qd434-ghc-native-bignum-9.6.1/lib/ghc-9.6.1/bin/../lib/x86_64-linux-ghc-9.6.1/libHSrts-1.0.2_thr-ghc9.6.1.so
(gdb) where
#0  0x00007fffef193a38 in interpretBCO ()
   from /nix/store/8lkbri2blncc4vh4rjqfc47jdx3qd434-ghc-native-bignum-9.6.1/lib/ghc-9.6.1/bin/../lib/x86_64-linux-ghc-9.6.1/libHSrts-1.0.2_thr-ghc9.6.1.so
#1  0x00007fffef1a232d in schedule ()
   from /nix/store/8lkbri2blncc4vh4rjqfc47jdx3qd434-ghc-native-bignum-9.6.1/lib/ghc-9.6.1/bin/../lib/x86_64-linux-ghc-9.6.1/libHSrts-1.0.2_thr-ghc9.6.1.so
#2  0x00007fffef1a288c in scheduleWorker ()
   from /nix/store/8lkbri2blncc4vh4rjqfc47jdx3qd434-ghc-native-bignum-9.6.1/lib/ghc-9.6.1/bin/../lib/x86_64-linux-ghc-9.6.1/libHSrts-1.0.2_thr-ghc9.6.1.so
#3  0x00007fffef1a6f0d in workerStart ()
   from /nix/store/8lkbri2blncc4vh4rjqfc47jdx3qd434-ghc-native-bignum-9.6.1/lib/ghc-9.6.1/bin/../lib/x86_64-linux-ghc-9.6.1/libHSrts-1.0.2_thr-ghc9.6.1.so
#4  0x00007fffeef7fe24 in start_thread () from /nix/store/1n2l5law9g3b77hcfyp50vrhhssbrj5g-glibc-2.37-8/lib/libc.so.6
#5  0x00007fffef0019b0 in clone3 () from /nix/store/1n2l5law9g3b77hcfyp50vrhhssbrj5g-glibc-2.37-8/lib/libc.so.6

Steps to reproduce

  1. Unpack tar xvf ghc-crash.tar.gz
  2. Run cabal repl
$ cabal repl ghc-crash:lib:ghc-crash --repl-no-load --repl-option -ghci-script=ghc-script.txt
Resolving dependencies...
Build profile: -w ghc-9.6.1 -O1
In order, the following will be built (use -v for more details):
 - ghc-crash-0.1 (lib) (first run)
Configuring library for ghc-crash-0.1..
Preprocessing library for ghc-crash-0.1..
GHCi, version 9.6.1: https://www.haskell.org/ghc/  :? for help

<no location info>: warning: [GHC-32850] [-Wmissing-home-modules]
    These modules are needed for compilation but not listed in your .cabal file's other-modules for ‘ghc-crash-0.1-inplace’ :
        TextFold
[1 of 2] Compiling TextFold
[2 of 2] Compiling GhcCrash
Ok, two modules loaded.
"Error: cabal: repl failed for ghc-crash-0.1. The build process segfaulted
(i.e. SIGSEGV).

Literal sources for reference and ease of inspection:

ghc-script.txt

:load GhcCrash.hs
:set -XOverloadedStrings
fileGlobsToRegex ["foo", "bar"]

GhcCrash.hs

{-# LANGUAGE CPP                 #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE KindSignatures      #-}
{-# LANGUAGE LinearTypes         #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}

module GhcCrash (fileGlobsToRegex) where

import Data.Text (Text)
import Data.Text.Builder.Linear.Buffer

-- Fails when imported, works if module is inlined in this one.
import TextFold

fileGlobsToRegex :: [Text] -> Text
fileGlobsToRegex patterns = runBuffer initRe
  where
    initRe :: Buffer %1 -> Buffer
    initRe buf =
      mkRe patterns (buf |>. '^') |>. '$'

    mkRe :: [Text] -> Buffer %1 -> Buffer
    mkRe []       buf = buf
    mkRe (x : xs) buf =
      mkRe' xs ((textFoldLinear f buf  x))

    mkRe' :: [Text] -> Buffer %1 -> Buffer
    mkRe' []       buf = buf
    mkRe' (x : xs) buf =
      mkRe' xs ((textFoldLinear f (buf |>. '|') x))

    f :: Char -> Buffer %1 -> Buffer
    f c buf = case c of
      '*'   -> buf |> ".*"
      other -> buf |>. other

TextFold.hs

{-# LANGUAGE BangPatterns        #-}
{-# LANGUAGE CPP                 #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE KindSignatures      #-}
{-# LANGUAGE LinearTypes         #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}

module TextFold (textFoldLinear) where

import Data.Text (Text)
import Data.Text.Internal qualified as TI
import Data.Text.Unsafe qualified as TU
import GHC.Exts (UnliftedType)

{-# INLINE textFoldLinear #-}
textFoldLinear :: forall (a :: UnliftedType). (Char -> a %1 -> a) -> a %1 -> Text -> a
textFoldLinear f seed (TI.Text arr off len) = textFoldLinearLoop seed 0 off
  where
    !end = off + len
    textFoldLinearLoop :: a %1 -> Int -> Int -> a
    textFoldLinearLoop x !i !j
      | j >= end  = x
      | otherwise =
        let TU.Iter c delta = TU.iterArray arr j
        in textFoldLinearLoop (f c x) (i + 1) (j + delta)

ghc-crash.cabal

cabal-version: 3.6

name: ghc-crash
version: 0.1

build-type:
  Simple

common ghc-options
  default-language:
    GHC2021

  default-extensions:
    LambdaCase

  ghc-options:
    -Weverything
    -Wno-all-missed-specialisations
    -Wno-implicit-prelude
    -Wno-missed-specialisations
    -Wno-missing-import-lists
    -Wno-missing-local-signatures
    -Wno-missing-safe-haskell-mode
    -Wno-safe
    -Wno-type-defaults
    -Wno-unsafe

  if impl(ghc >= 8.8)
    ghc-options:
      -Wno-missing-deriving-strategies

  if impl(ghc >= 9.2)
    ghc-options:
      -Wno-missing-kind-signatures

library
  import: ghc-options
  exposed-modules:
    GhcCrash
    TextFold
  hs-source-dirs:
    .
  build-depends:
    , base >= 4.16
    , text
    , text-builder-linear

Expected behavior

No segmentation fault, ghci outputs ^foo|bar$.

Environment

  • GHC version used: 9.6.1 without GMP
  • Operating System: NixOS
  • System Architecture: x86_64
Edited by Sergey Vinokurov
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information