Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
4,247
Issues
4,247
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
398
Merge Requests
398
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
2844abb4
Commit
2844abb4
authored
Jul 20, 2012
by
Ian Lynagh
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
GHC 7.4 is now required for building HEAD
parent
8a133440
Changes
23
Hide whitespace changes
Inline
Side-by-side
Showing
23 changed files
with
2 additions
and
403 deletions
+2
-403
compiler/cmm/Cmm.hs
compiler/cmm/Cmm.hs
+0
-5
compiler/cmm/CmmBuildInfoTables.hs
compiler/cmm/CmmBuildInfoTables.hs
+0
-4
compiler/cmm/CmmLayoutStack.hs
compiler/cmm/CmmLayoutStack.hs
+0
-3
compiler/cmm/CmmLint.hs
compiler/cmm/CmmLint.hs
+0
-3
compiler/cmm/CmmNode.hs
compiler/cmm/CmmNode.hs
+0
-6
compiler/cmm/CmmProcPoint.hs
compiler/cmm/CmmProcPoint.hs
+0
-3
compiler/cmm/CmmUtils.hs
compiler/cmm/CmmUtils.hs
+0
-5
compiler/cmm/Hoopl.hs
compiler/cmm/Hoopl.hs
+0
-3
compiler/cmm/Hoopl/Dataflow.hs
compiler/cmm/Hoopl/Dataflow.hs
+0
-7
compiler/cmm/PprC.hs
compiler/cmm/PprC.hs
+0
-4
compiler/coreSyn/CoreLint.lhs
compiler/coreSyn/CoreLint.lhs
+0
-2
compiler/ghc.cabal.in
compiler/ghc.cabal.in
+0
-1
compiler/main/InteractiveEval.hs
compiler/main/InteractiveEval.hs
+0
-4
compiler/main/SysTools.lhs
compiler/main/SysTools.lhs
+0
-8
compiler/nativeGen/PprBase.hs
compiler/nativeGen/PprBase.hs
+0
-5
compiler/utils/Binary.hs
compiler/utils/Binary.hs
+0
-12
compiler/utils/FastString.lhs
compiler/utils/FastString.lhs
+0
-4
compiler/utils/Fingerprint.hsc
compiler/utils/Fingerprint.hsc
+0
-64
compiler/utils/Outputable.lhs
compiler/utils/Outputable.lhs
+0
-7
compiler/utils/Panic.lhs
compiler/utils/Panic.lhs
+0
-6
compiler/utils/StringBuffer.lhs
compiler/utils/StringBuffer.lhs
+0
-4
compiler/utils/md5.c
compiler/utils/md5.c
+0
-241
configure.ac
configure.ac
+2
-2
No files found.
compiler/cmm/Cmm.hs
View file @
2844abb4
-- Cmm representations using Hoopl's Graph CmmNode e x.
{-# LANGUAGE GADTs #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
if
__GLASGOW_HASKELL__
>=
703
-- GHC 7.0.1 improved incomplete pattern warnings with GADTs
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
#
endif
module
Cmm
(
-- * Cmm top-level datatypes
...
...
compiler/cmm/CmmBuildInfoTables.hs
View file @
2844abb4
...
...
@@ -48,11 +48,7 @@ import qualified Data.Set as Set
import
Control.Monad
foldSet
::
(
a
->
b
->
b
)
->
b
->
Set
a
->
b
#
if
__GLASGOW_HASKELL__
<
704
foldSet
=
Set
.
fold
#
else
foldSet
=
Set
.
foldr
#
endif
----------------------------------------------------------------
-- Building InfoTables
...
...
compiler/cmm/CmmLayoutStack.hs
View file @
2844abb4
{-# LANGUAGE RecordWildCards, GADTs #-}
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
CmmLayoutStack
(
cmmLayoutStack
,
setInfoTableStackMap
)
where
...
...
compiler/cmm/CmmLint.hs
View file @
2844abb4
...
...
@@ -6,9 +6,6 @@
--
-----------------------------------------------------------------------------
{-# LANGUAGE GADTs #-}
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
CmmLint
(
cmmLint
,
cmmLintGraph
)
where
...
...
compiler/cmm/CmmNode.hs
View file @
2844abb4
...
...
@@ -8,12 +8,6 @@
-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
-- for details
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
if
__GLASGOW_HASKELL__
>=
703
-- GHC 7.0.1 improved incomplete pattern warnings with GADTs
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
#
endif
module
CmmNode
(
CmmNode
(
..
),
ForeignHint
(
..
),
CmmFormal
,
CmmActual
,
UpdFrameOffset
,
Convention
(
..
),
ForeignConvention
(
..
),
ForeignTarget
(
..
),
...
...
compiler/cmm/CmmProcPoint.hs
View file @
2844abb4
{-# LANGUAGE GADTs, DisambiguateRecordFields #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
CmmProcPoint
(
ProcPointSet
,
Status
(
..
)
...
...
compiler/cmm/CmmUtils.hs
View file @
2844abb4
...
...
@@ -8,11 +8,6 @@
{-# OPTIONS_GHC -fno-warn-deprecations #-}
-- Warnings from deprecated blockToNodeList
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
if
__GLASGOW_HASKELL__
>=
703
-- GHC 7.0.1 improved incomplete pattern warnings with GADTs
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
#
endif
-----------------------------------------------------------------------------
...
...
compiler/cmm/Hoopl.hs
View file @
2844abb4
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
#
endif
module
Hoopl
(
module
Compiler
.
Hoopl
,
module
Hoopl
.
Dataflow
,
...
...
compiler/cmm/Hoopl/Dataflow.hs
View file @
2844abb4
...
...
@@ -10,15 +10,8 @@
--
{-# LANGUAGE RankNTypes, ScopedTypeVariables, GADTs, EmptyDataDecls, PatternGuards, TypeFamilies, MultiParamTypeClasses #-}
#
if
__GLASGOW_HASKELL__
>=
703
{-# OPTIONS_GHC -fprof-auto-top #-}
#
endif
#
if
__GLASGOW_HASKELL__
>=
701
{-# LANGUAGE Trustworthy #-}
#
endif
#
if
__GLASGOW_HASKELL__
<
701
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
#
endif
module
Hoopl.Dataflow
(
DataflowLattice
(
..
),
OldFact
(
..
),
NewFact
(
..
),
Fact
,
mkFactBase
...
...
compiler/cmm/PprC.hs
View file @
2844abb4
...
...
@@ -51,12 +51,8 @@ import Data.Word
import
System.IO
import
qualified
Data.Map
as
Map
#
if
__GLASGOW_HASKELL__
>=
703
import
Data.Array.Unsafe
(
castSTUArray
)
import
Data.Array.ST
hiding
(
castSTUArray
)
#
else
import
Data.Array.ST
#
endif
-- --------------------------------------------------------------------------
-- Top level
...
...
compiler/coreSyn/CoreLint.lhs
View file @
2844abb4
...
...
@@ -14,9 +14,7 @@ A ``lint'' pass to check for Core correctness
-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
-- for details
#if __GLASGOW_HASKELL__ >= 704
{-# OPTIONS_GHC -fprof-auto #-}
#endif
module CoreLint ( lintCoreBindings, lintUnfolding ) where
...
...
compiler/ghc.cabal.in
View file @
2844abb4
...
...
@@ -100,7 +100,6 @@ Library
c-sources:
parser/cutils.c
utils/md5.c
if flag(dynlibs)
c-sources:
...
...
compiler/main/InteractiveEval.hs
View file @
2844abb4
...
...
@@ -76,11 +76,7 @@ import Data.Dynamic
import
Data.Either
import
Data.List
(
find
)
import
Control.Monad
#
if
__GLASGOW_HASKELL__
>=
701
import
Foreign.Safe
#
else
import
Foreign
hiding
(
unsafePerformIO
)
#
endif
import
Foreign.C
import
GHC.Exts
import
Data.Array
...
...
compiler/main/SysTools.lhs
View file @
2844abb4
...
...
@@ -596,7 +596,6 @@ copyWithHeader dflags purpose maybe_header from to = do
hClose hout
hClose hin
where
#if __GLASGOW_HASKELL__ >= 702
-- write the header string in UTF-8. The header is something like
-- {-# LINE "foo.hs" #-}
-- and we want to make sure a Unicode filename isn't mangled.
...
...
@@ -604,9 +603,6 @@ copyWithHeader dflags purpose maybe_header from to = do
hSetEncoding h utf8
hPutStr h str
hSetBinaryMode h True
#else
header h str = hPutStr h str
#endif
-- | read the contents of the named section in an ELF object as a
-- String.
...
...
@@ -782,11 +778,7 @@ runSomethingWith
runSomethingWith dflags phase_name pgm args io = do
let real_args = filter notNull (map showOpt args)
#if __GLASGOW_HASKELL__ >= 701
cmdLine = showCommandForUser pgm real_args
#else
cmdLine = unwords (pgm:real_args)
#endif
traceCmd dflags phase_name cmdLine $ handleProc pgm phase_name $ io real_args
handleProc :: String -> String -> IO (ExitCode, r) -> IO r
...
...
compiler/nativeGen/PprBase.hs
View file @
2844abb4
...
...
@@ -22,13 +22,8 @@ module PprBase (
where
-- castSTUArray has moved to Data.Array.Unsafe
#
if
__GLASGOW_HASKELL__
>=
703
import
Data.Array.Unsafe
(
castSTUArray
)
import
Data.Array.ST
hiding
(
castSTUArray
)
#
else
import
Data.Array.ST
#
endif
import
Control.Monad.ST
...
...
compiler/utils/Binary.hs
View file @
2844abb4
...
...
@@ -78,9 +78,7 @@ import Data.IORef
import
Data.Char
(
ord
,
chr
)
import
Data.Time
import
Data.Typeable
#
if
__GLASGOW_HASKELL__
>=
701
import
Data.Typeable.Internal
#
endif
import
Control.Monad
(
when
)
import
System.IO
as
IO
import
System.IO.Unsafe
(
unsafeInterleaveIO
)
...
...
@@ -604,22 +602,12 @@ instance Binary (Bin a) where
-- -----------------------------------------------------------------------------
-- Instances for Data.Typeable stuff
#
if
__GLASGOW_HASKELL__
>=
701
instance
Binary
TyCon
where
put_
bh
(
TyCon
_
p
m
n
)
=
do
put_
bh
(
p
,
m
,
n
)
get
bh
=
do
(
p
,
m
,
n
)
<-
get
bh
return
(
mkTyCon3
p
m
n
)
#
else
instance
Binary
TyCon
where
put_
bh
ty_con
=
do
let
s
=
tyConString
ty_con
put_
bh
s
get
bh
=
do
s
<-
get
bh
return
(
mkTyCon
s
)
#
endif
instance
Binary
TypeRep
where
put_
bh
type_rep
=
do
...
...
compiler/utils/FastString.lhs
View file @
2844abb4
...
...
@@ -119,11 +119,7 @@ import Data.Char
import GHC.IO ( IO(..) )
#if __GLASGOW_HASKELL__ >= 701
import Foreign.Safe
#else
import Foreign hiding ( unsafePerformIO )
#endif
#if defined(__GLASGOW_HASKELL__)
import GHC.Base ( unpackCString# )
...
...
compiler/utils/Fingerprint.hsc
View file @
2844abb4
...
...
@@ -24,71 +24,7 @@ import Outputable
import Text.Printf
import Numeric ( readHex )
##if __GLASGOW_HASKELL__ >= 701
-- The MD5 implementation is now in base, to support Typeable
import GHC.Fingerprint
##endif
##if __GLASGOW_HASKELL__ < 701
import Data.Char
import Foreign
import Foreign.C
import GHC.IO (unsafeDupablePerformIO)
-- Using 128-bit MD5 fingerprints for now.
data Fingerprint = Fingerprint {-# UNPACK #-} !Word64 {-# UNPACK #-} !Word64
deriving (Eq, Ord)
-- or ByteString?
fingerprint0 :: Fingerprint
fingerprint0 = Fingerprint 0 0
peekFingerprint :: Ptr Word8 -> IO Fingerprint
peekFingerprint p = do
let peekW64 :: Ptr Word8 -> Int -> Word64 -> IO Word64
STRICT3(peekW64)
peekW64 _ 0 i = return i
peekW64 p n i = do
w8 <- peek p
peekW64 (p `plusPtr` 1) (n-1)
((i `shiftL` 8) .|. fromIntegral w8)
high <- peekW64 p 8 0
low <- peekW64 (p `plusPtr` 8) 8 0
return (Fingerprint high low)
fingerprintData :: Ptr Word8 -> Int -> IO Fingerprint
fingerprintData buf len = do
allocaBytes (#const sizeof(struct MD5Context)) $ \pctxt -> do
c_MD5Init pctxt
c_MD5Update pctxt buf (fromIntegral len)
allocaBytes 16 $ \pdigest -> do
c_MD5Final pdigest pctxt
peekFingerprint (castPtr pdigest)
-- This is duplicated in libraries/base/GHC/Fingerprint.hs
fingerprintString :: String -> Fingerprint
fingerprintString str = unsafeDupablePerformIO $
withArrayLen word8s $ \len p ->
fingerprintData p len
where word8s = concatMap f str
f c = let w32 :: Word32
w32 = fromIntegral (ord c)
in [fromIntegral (w32 `shiftR` 24),
fromIntegral (w32 `shiftR` 16),
fromIntegral (w32 `shiftR` 8),
fromIntegral w32]
data MD5Context
foreign import ccall unsafe "MD5Init"
c_MD5Init :: Ptr MD5Context -> IO ()
foreign import ccall unsafe "MD5Update"
c_MD5Update :: Ptr MD5Context -> Ptr Word8 -> CInt -> IO ()
foreign import ccall unsafe "MD5Final"
c_MD5Final :: Ptr Word8 -> Ptr MD5Context -> IO ()
##endif
instance Outputable Fingerprint where
ppr (Fingerprint w1 w2) = text (printf "%016x%016x" w1 w2)
...
...
compiler/utils/Outputable.lhs
View file @
2844abb4
...
...
@@ -93,14 +93,7 @@ import Data.Word
import System.IO ( Handle )
import System.FilePath
#if __GLASGOW_HASKELL__ >= 701
import GHC.Show ( showMultiLineString )
#else
showMultiLineString :: String -> [String]
-- Crude version
showMultiLineString s = [ showList s "" ]
#endif
\end{code}
...
...
compiler/utils/Panic.lhs
View file @
2844abb4
...
...
@@ -47,9 +47,7 @@ import System.Posix.Signals
import GHC.ConsoleHandler
#endif
#if __GLASGOW_HASKELL__ >= 703
import GHC.Stack
#endif
#if __GLASGOW_HASKELL__ >= 705
import System.Mem.Weak ( Weak, deRefWeak )
...
...
@@ -188,15 +186,11 @@ handleGhcException = ghandle
-- | Panics and asserts.
panic, sorry, pgmError :: String -> a
#if __GLASGOW_HASKELL__ >= 703
panic x = unsafeDupablePerformIO $ do
stack <- ccsToStrings =<< getCurrentCCS x
if null stack
then throwGhcException (Panic x)
else throwGhcException (Panic (x ++ '\n' : renderStack stack))
#else
panic x = throwGhcException (Panic x)
#endif
sorry x = throwGhcException (Sorry x)
pgmError x = throwGhcException (ProgramError x)
...
...
compiler/utils/StringBuffer.lhs
View file @
2844abb4
...
...
@@ -54,11 +54,7 @@ import System.IO.Unsafe ( unsafePerformIO )
import GHC.Exts
#if __GLASGOW_HASKELL__ >= 701
import Foreign.Safe
#else
import Foreign hiding ( unsafePerformIO )
#endif
-- -----------------------------------------------------------------------------
-- The StringBuffer type
...
...
compiler/utils/md5.c
deleted
100644 → 0
View file @
8a133440
/*
* This code implements the MD5 message-digest algorithm.
* The algorithm is due to Ron Rivest. This code was
* written by Colin Plumb in 1993, no copyright is claimed.
* This code is in the public domain; do with it what you wish.
*
* Equivalent code is available from RSA Data Security, Inc.
* This code has been tested against that, and is equivalent,
* except that you don't need to include two pages of legalese
* with every copy.
*
* To compute the message digest of a chunk of bytes, declare an
* MD5Context structure, pass it to MD5Init, call MD5Update as
* needed on buffers full of bytes, and then call MD5Final, which
* will fill a supplied 16-byte array with the digest.
*/
#if __GLASGOW_HASKELL__ < 701
#include "HsFFI.h"
#include "md5.h"
#include <string.h>
void
MD5Init
(
struct
MD5Context
*
context
);
void
MD5Update
(
struct
MD5Context
*
context
,
byte
const
*
buf
,
int
len
);
void
MD5Final
(
byte
digest
[
16
],
struct
MD5Context
*
context
);
void
MD5Transform
(
word32
buf
[
4
],
word32
const
in
[
16
]);
/*
* Shuffle the bytes into little-endian order within words, as per the
* MD5 spec. Note: this code works regardless of the byte order.
*/
void
byteSwap
(
word32
*
buf
,
unsigned
words
)
{
byte
*
p
=
(
byte
*
)
buf
;
do
{
*
buf
++
=
(
word32
)((
unsigned
)
p
[
3
]
<<
8
|
p
[
2
])
<<
16
|
((
unsigned
)
p
[
1
]
<<
8
|
p
[
0
]);
p
+=
4
;
}
while
(
--
words
);
}
/*
* Start MD5 accumulation. Set bit count to 0 and buffer to mysterious
* initialization constants.
*/
void
MD5Init
(
struct
MD5Context
*
ctx
)
{
ctx
->
buf
[
0
]
=
0x67452301
;
ctx
->
buf
[
1
]
=
0xefcdab89
;
ctx
->
buf
[
2
]
=
0x98badcfe
;
ctx
->
buf
[
3
]
=
0x10325476
;
ctx
->
bytes
[
0
]
=
0
;
ctx
->
bytes
[
1
]
=
0
;
}
/*
* Update context to reflect the concatenation of another buffer full
* of bytes.
*/
void
MD5Update
(
struct
MD5Context
*
ctx
,
byte
const
*
buf
,
int
len
)
{
word32
t
;
/* Update byte count */
t
=
ctx
->
bytes
[
0
];
if
((
ctx
->
bytes
[
0
]
=
t
+
len
)
<
t
)
ctx
->
bytes
[
1
]
++
;
/* Carry from low to high */
t
=
64
-
(
t
&
0x3f
);
/* Space available in ctx->in (at least 1) */
if
((
unsigned
)
t
>
len
)
{
memcpy
((
byte
*
)
ctx
->
in
+
64
-
(
unsigned
)
t
,
buf
,
len
);
return
;
}
/* First chunk is an odd size */
memcpy
((
byte
*
)
ctx
->
in
+
64
-
(
unsigned
)
t
,
buf
,
(
unsigned
)
t
);
byteSwap
(
ctx
->
in
,
16
);
MD5Transform
(
ctx
->
buf
,
ctx
->
in
);
buf
+=
(
unsigned
)
t
;
len
-=
(
unsigned
)
t
;
/* Process data in 64-byte chunks */
while
(
len
>=
64
)
{
memcpy
(
ctx
->
in
,
buf
,
64
);
byteSwap
(
ctx
->
in
,
16
);
MD5Transform
(
ctx
->
buf
,
ctx
->
in
);
buf
+=
64
;
len
-=
64
;
}
/* Handle any remaining bytes of data. */
memcpy
(
ctx
->
in
,
buf
,
len
);
}
/*
* Final wrapup - pad to 64-byte boundary with the bit pattern
* 1 0* (64-bit count of bits processed, MSB-first)
*/
void
MD5Final
(
byte
digest
[
16
],
struct
MD5Context
*
ctx
)
{
int
count
=
(
int
)(
ctx
->
bytes
[
0
]
&
0x3f
);
/* Bytes in ctx->in */
byte
*
p
=
(
byte
*
)
ctx
->
in
+
count
;
/* First unused byte */
/* Set the first char of padding to 0x80. There is always room. */
*
p
++
=
0x80
;
/* Bytes of padding needed to make 56 bytes (-8..55) */
count
=
56
-
1
-
count
;
if
(
count
<
0
)
{
/* Padding forces an extra block */
memset
(
p
,
0
,
count
+
8
);
byteSwap
(
ctx
->
in
,
16
);
MD5Transform
(
ctx
->
buf
,
ctx
->
in
);
p
=
(
byte
*
)
ctx
->
in
;
count
=
56
;
}
memset
(
p
,
0
,
count
+
8
);
byteSwap
(
ctx
->
in
,
14
);
/* Append length in bits and transform */
ctx
->
in
[
14
]
=
ctx
->
bytes
[
0
]
<<
3
;
ctx
->
in
[
15
]
=
ctx
->
bytes
[
1
]
<<
3
|
ctx
->
bytes
[
0
]
>>
29
;
MD5Transform
(
ctx
->
buf
,
ctx
->
in
);
byteSwap
(
ctx
->
buf
,
4
);
memcpy
(
digest
,
ctx
->
buf
,
16
);
memset
(
ctx
,
0
,
sizeof
(
ctx
));
}
/* The four core functions - F1 is optimized somewhat */
/* #define F1(x, y, z) (x & y | ~x & z) */
#define F1(x, y, z) (z ^ (x & (y ^ z)))
#define F2(x, y, z) F1(z, x, y)
#define F3(x, y, z) (x ^ y ^ z)
#define F4(x, y, z) (y ^ (x | ~z))
/* This is the central step in the MD5 algorithm. */
#define MD5STEP(f,w,x,y,z,in,s) \
(w += f(x,y,z) + in, w = (w<<s | w>>(32-s)) + x)
/*
* The core of the MD5 algorithm, this alters an existing MD5 hash to
* reflect the addition of 16 longwords of new data. MD5Update blocks
* the data and converts bytes into longwords for this routine.
*/
void
MD5Transform
(
word32
buf
[
4
],
word32
const
in
[
16
])
{
register
word32
a
,
b
,
c
,
d
;
a
=
buf
[
0
];
b
=
buf
[
1
];
c
=
buf
[
2
];
d
=
buf
[
3
];
MD5STEP
(
F1
,
a
,
b
,
c
,
d
,
in
[
0
]
+
0xd76aa478
,
7
);
MD5STEP
(
F1
,
d
,
a
,
b
,
c
,
in
[
1
]
+
0xe8c7b756
,
12
);
MD5STEP
(
F1
,
c
,
d
,
a
,
b
,
in
[
2
]
+
0x242070db
,
17
);
MD5STEP
(
F1
,
b
,
c
,
d
,
a
,
in
[
3
]
+
0xc1bdceee
,
22
);
MD5STEP
(
F1
,
a
,
b
,
c
,
d
,
in
[
4
]
+
0xf57c0faf
,
7
);
MD5STEP
(
F1
,
d
,
a
,
b
,
c
,
in
[
5
]
+
0x4787c62a
,
12
);
MD5STEP
(
F1
,
c
,
d
,
a
,
b
,
in
[
6
]
+
0xa8304613
,
17
);
MD5STEP
(
F1
,
b
,
c
,
d
,
a
,
in
[
7
]
+
0xfd469501
,
22
);
MD5STEP
(
F1
,
a
,
b
,
c
,
d
,
in
[
8
]
+
0x698098d8
,
7
);
MD5STEP
(
F1
,
d
,
a
,
b
,
c
,
in
[
9
]
+
0x8b44f7af
,
12
);
MD5STEP
(
F1
,
c
,
d
,
a
,
b
,
in
[
10
]
+
0xffff5bb1
,
17
);
MD5STEP
(
F1
,
b
,
c
,
d
,
a
,
in
[
11
]
+
0x895cd7be
,
22
);
MD5STEP
(
F1
,
a
,
b
,
c
,
d
,
in
[
12
]
+
0x6b901122
,
7
);
MD5STEP
(
F1
,
d
,
a
,
b
,
c
,
in
[
13
]
+
0xfd987193
,
12
);
MD5STEP
(
F1
,
c
,
d
,
a
,
b
,
in
[
14
]
+
0xa679438e
,
17
);
MD5STEP
(
F1
,
b
,
c
,
d
,
a
,
in
[
15
]
+
0x49b40821
,
22
);
MD5STEP
(
F2
,
a
,
b
,
c
,
d
,
in
[
1
]
+
0xf61e2562
,
5
);
MD5STEP
(
F2
,
d
,
a
,
b
,
c
,
in
[
6
]
+
0xc040b340
,
9
);
MD5STEP
(
F2
,
c
,
d
,
a
,
b
,
in
[
11
]
+
0x265e5a51
,
14
);
MD5STEP
(
F2
,
b
,
c
,
d
,
a
,
in
[
0
]
+
0xe9b6c7aa
,
20
);
MD5STEP
(
F2
,
a
,
b
,
c
,
d
,
in
[
5
]
+
0xd62f105d
,
5
);
MD5STEP
(
F2
,
d
,
a
,
b
,
c
,
in
[
10
]
+
0x02441453
,
9
);
MD5STEP
(
F2
,
c
,
d
,
a
,
b
,
in
[
15
]
+
0xd8a1e681
,
14
);
MD5STEP
(
F2
,
b
,
c
,
d
,
a
,
in
[
4
]
+
0xe7d3fbc8
,
20
);
MD5STEP
(
F2
,
a
,
b
,
c
,
d
,
in
[
9
]
+
0x21e1cde6
,
5
);
MD5STEP
(
F2
,
d
,
a
,
b
,
c
,
in
[
14
]
+
0xc33707d6
,
9
);
MD5STEP
(
F2
,
c
,
d
,
a
,
b
,
in
[
3
]
+
0xf4d50d87
,
14
);
MD5STEP
(
F2
,
b
,
c
,
d
,
a
,
in
[
8
]
+
0x455a14ed
,
20
);
MD5STEP
(
F2
,
a
,
b
,
c
,
d
,
in
[
13
]
+
0xa9e3e905
,
5
);
MD5STEP
(
F2
,
d
,
a
,
b
,
c
,
in
[
2
]
+
0xfcefa3f8
,
9
);
MD5STEP
(
F2
,
c
,
d
,
a
,
b
,
in
[
7
]
+
0x676f02d9
,
14
);
MD5STEP
(
F2
,
b
,
c
,
d
,
a
,
in
[
12
]
+
0x8d2a4c8a
,
20
);
MD5STEP
(
F3
,
a
,
b
,
c
,
d
,
in
[
5
]
+
0xfffa3942
,
4
);
MD5STEP
(
F3
,
d
,
a
,
b
,
c
,
in
[
8
]
+
0x8771f681
,
11
);
MD5STEP
(
F3
,
c
,
d
,
a
,
b
,
in
[
11
]
+
0x6d9d6122
,
16
);
MD5STEP
(
F3
,
b
,
c
,
d
,
a
,
in
[
14
]
+
0xfde5380c
,
23
);
MD5STEP
(
F3
,
a
,
b
,
c
,
d
,
in
[
1
]
+
0xa4beea44
,
4
);
MD5STEP
(
F3
,
d
,
a
,
b
,
c
,
in
[
4
]
+
0x4bdecfa9
,
11
);
MD5STEP
(
F3
,
c
,
d
,
a
,
b
,
in
[
7
]
+
0xf6bb4b60
,
16
);
MD5STEP
(
F3
,
b
,
c
,
d
,
a
,
in
[
10
]
+
0xbebfbc70
,
23
);
MD5STEP
(
F3
,
a
,
b
,
c
,
d
,
in
[
13
]
+
0x289b7ec6
,
4
);
MD5STEP
(
F3
,
d
,
a
,
b
,
c
,
in
[
0
]
+
0xeaa127fa
,
11
);
MD5STEP
(
F3
,
c
,
d
,
a
,
b
,
in
[
3
]
+
0xd4ef3085
,
16
);
MD5STEP
(
F3
,
b
,
c
,
d
,
a
,
in
[
6
]
+
0x04881d05
,
23
);
MD5STEP
(
F3
,
a
,
b
,
c
,
d
,
in
[
9
]
+
0xd9d4d039
,
4
);
MD5STEP
(
F3
,
d
,
a
,
b
,
c
,
in
[
12
]
+
0xe6db99e5
,
11
);
MD5STEP
(
F3
,
c
,
d
,
a
,
b
,
in
[
15
]
+
0x1fa27cf8
,
16
);
MD5STEP
(
F3
,
b
,
c
,
d
,
a
,
in
[
2
]
+
0xc4ac5665
,
23
);
MD5STEP
(
F4
,
a
,
b
,
c
,
d
,
in
[
0
]
+
0xf4292244
,
6
);
MD5STEP
(
F4
,
d
,
a
,
b
,
c
,
in
[
7
]
+
0x432aff97
,
10
);
MD5STEP
(
F4
,
c
,
d
,
a
,
b
,
in
[
14
]
+
0xab9423a7
,
15
);
MD5STEP
(
F4
,
b
,
c
,
d
,
a
,
in
[
5
]
+
0xfc93a039
,
21
);
MD5STEP
(
F4
,
a
,
b
,
c
,
d
,
in
[
12
]
+
0x655b59c3
,
6
);
MD5STEP
(
F4
,
d
,
a
,
b
,
c
,
in
[
3
]
+
0x8f0ccc92
,
10
);
MD5STEP
(
F4
,
c
,
d
,
a
,
b
,
in
[
10
]
+
0xffeff47d
,
15
);
MD5STEP
(
F4
,
b
,
c
,
d
,
a
,
in
[
1
]
+
0x85845dd1
,
21
);
MD5STEP
(
F4
,
a
,
b
,
c
,
d
,
in
[
8
]
+
0x6fa87e4f
,
6
);
MD5STEP
(
F4
,
d
,
a
,
b
,
c
,
in
[
15
]
+
0xfe2ce6e0
,
10
);
MD5STEP
(
F4
,
c
,
d
,
a
,
b
,
in
[
6
]
+
0xa3014314
,
15
);
MD5STEP
(
F4
,
b
,
c
,
d
,
a
,
in
[
13
]
+
0x4e0811a1
,
21
);
MD5STEP
(
F4
,
a
,
b
,
c
,
d
,
in
[
4
]
+
0xf7537e82
,
6
);
MD5STEP
(
F4
,
d
,
a
,
b
,
c
,
in
[
11
]
+
0xbd3af235
,
10
);
MD5STEP
(
F4
,
c
,
d
,
a
,
b
,
in
[
2
]
+
0x2ad7d2bb
,
15
);
MD5STEP
(
F4
,
b
,
c
,
d
,
a
,
in
[
9
]
+
0xeb86d391
,
21
);
buf
[
0
]
+=
a
;
buf
[
1
]
+=
b
;
buf
[
2
]
+=
c
;
buf
[
3
]
+=
d
;
}
#endif
configure.ac
View file @
2844abb4
...
...
@@ -149,8 +149,8 @@ if test "$BootingFromHc" = "NO"; then
if test "$WithGhc" = ""; then
AC_MSG_ERROR([GHC is required unless bootstrapping from .hc files.])
fi
FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[7.
0
],
[AC_MSG_ERROR([GHC version 7.
0
or later is required to compile GHC.])])dnl
FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[7.
4
],
[AC_MSG_ERROR([GHC version 7.
4
or later is required to compile GHC.])])dnl
if test `expr $GhcMinVersion % 2` = "1"; then
if test "$EnableBootstrapWithDevelSnaphost" = "NO"; then
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment