File: FastFunctions.hs

package info (click to toggle)
ghc 8.4.4%2Bdfsg1-3
  • links: PTS, VCS
  • area: main
  • in suites: buster
  • size: 67,548 kB
  • sloc: haskell: 435,629; ansic: 62,017; sh: 6,706; python: 1,916; makefile: 1,014; perl: 465; asm: 315; xml: 196; yacc: 102; ruby: 84; lisp: 7
file content (21 lines) | stat: -rw-r--r-- 412 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
{-
(c) The University of Glasgow, 2000-2006
-}

{-# LANGUAGE CPP, MagicHash, UnboxedTuples #-}

module FastFunctions (
    inlinePerformIO,
  ) where

#include "HsVersions.h"

import GhcPrelude ()

import GHC.Exts
import GHC.IO   (IO(..))

-- Just like unsafePerformIO, but we inline it.
{-# INLINE inlinePerformIO #-}
inlinePerformIO :: IO a -> a
inlinePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r