summaryrefslogtreecommitdiff
path: root/ghc/compiler/nativeGen/StixInteger.lhs
blob: f0e9905d0c127ca36c29e7c19c5807d50f98a09b (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
%
% (c) The AQUA Project, Glasgow University, 1993-1998
%

\begin{code}
module StixInteger ( 
	gmpCompare, 
        gmpCompareInt,
	gmpInteger2Int, 
	gmpInteger2Word,
	gmpNegate
	) where

#include "HsVersions.h"

import {-# SOURCE #-} StixPrim ( amodeToStix )

import AbsCSyn		hiding (spRel) -- bits and bobs..
import CallConv		( cCallConv )
import PrimOp		( PrimOp(..) )
import PrimRep		( PrimRep(..) )
import Stix		( StixTree(..), StixTreeList, arrWordsHS )
import UniqSupply	( returnUs, UniqSM )
\end{code}

Although gmpCompare doesn't allocate space, it does temporarily use
some space just beyond the heap pointer.  This is safe, because the
enclosing routine has already guaranteed that this space will be
available.  (See ``primOpHeapRequired.'')

\begin{code}
stgArrWords__words        :: StixTree -> StixTree
stgArrWords__BYTE_ARR_CTS :: StixTree -> StixTree

stgArrWords__BYTE_ARR_CTS arr 
   = StIndex WordRep arr arrWordsHS
stgArrWords__words        arr 
   = case arrWordsHS of 
        StInt i -> StInd WordRep (StIndex PtrRep arr (StInt (i-1)))

gmpCompare
    :: CAddrMode    	    -- result (boolean)
    -> (CAddrMode,CAddrMode,CAddrMode,CAddrMode)
    		  	    -- alloc hp + 2 arguments (2 parts each)
    -> UniqSM StixTreeList

gmpCompare res args@(csa1,cda1, csa2,cda2)
  = let
	result	= amodeToStix res
	sa1	= amodeToStix csa1
	sa2	= amodeToStix csa2
	aa1	= stgArrWords__words (amodeToStix cda1)
	aa2	= stgArrWords__words (amodeToStix cda2)
	da1	= stgArrWords__BYTE_ARR_CTS (amodeToStix cda1)
	da2	= stgArrWords__BYTE_ARR_CTS (amodeToStix cda2)

    	(a1,a2,a3) = toStruct scratch1 (aa1,sa1,da1)
    	(a4,a5,a6) = toStruct scratch2 (aa2,sa2,da2)
    	mpz_cmp = StCall SLIT("__gmpz_cmp") cCallConv IntRep [scratch1, scratch2]
    	r1 = StAssign IntRep result mpz_cmp
    in
    returnUs (\xs -> a1 : a2 : a3 : a4 : a5 : a6 : r1 : xs)


gmpCompareInt
    :: CAddrMode    	    -- result (boolean)
    -> (CAddrMode,CAddrMode,CAddrMode)
    -> UniqSM StixTreeList  -- alloc hp + 1 arg (??)

gmpCompareInt res args@(csa1,cda1, cai)
  = let
	result	 = amodeToStix res
	sa1	 = amodeToStix csa1
	aa1	 = stgArrWords__words (amodeToStix cda1)
	da1	 = stgArrWords__BYTE_ARR_CTS (amodeToStix cda1)
        ai       = amodeToStix cai
    	(a1,a2,a3) = toStruct scratch1 (aa1,sa1,da1)
    	mpz_cmp_si = StCall SLIT("__gmpz_cmp_si") cCallConv IntRep [scratch1, ai]
    	r1 = StAssign IntRep result mpz_cmp_si
    in
    returnUs (\xs -> a1 : a2 : a3 : r1 : xs)
\end{code}

\begin{code}
gmpInteger2Int
    :: CAddrMode    	    -- result
    -> (CAddrMode,CAddrMode) -- alloc hp + argument (2 parts)
    -> UniqSM StixTreeList

gmpInteger2Int res args@(csa,cda)
  = let
	result	= amodeToStix res
	sa	= amodeToStix csa
	aa	= stgArrWords__words (amodeToStix cda)
	da	= stgArrWords__BYTE_ARR_CTS (amodeToStix cda)

    	(a1,a2,a3) = toStruct scratch1 (aa,sa,da)
    	mpz_get_si = StCall SLIT("__gmpz_get_si") cCallConv IntRep [scratch1]
    	r1 = StAssign IntRep result mpz_get_si
    in
    returnUs (\xs -> a1 : a2 : a3 : r1 : xs)

gmpInteger2Word
    :: CAddrMode    	    -- result
    -> (CAddrMode,CAddrMode) -- alloc hp + argument (2 parts)
    -> UniqSM StixTreeList

gmpInteger2Word res args@(csa,cda)
  = let
	result	= amodeToStix res
	sa	= amodeToStix csa
	aa	= stgArrWords__words (amodeToStix cda)
	da	= stgArrWords__BYTE_ARR_CTS (amodeToStix cda)

    	(a1,a2,a3) = toStruct scratch1 (aa,sa,da)
    	mpz_get_ui = StCall SLIT("__gmpz_get_ui") cCallConv IntRep [scratch1]
    	r1 = StAssign WordRep result mpz_get_ui
    in
    returnUs (\xs -> a1 : a2 : a3 : r1 : xs)

gmpNegate
    :: (CAddrMode,CAddrMode) -- result
    -> (CAddrMode,CAddrMode) -- argument (2 parts)
    -> UniqSM StixTreeList

gmpNegate (rcs, rcd) args@(cs, cd)
  = let
	s	= amodeToStix cs
	a	= stgArrWords__words (amodeToStix cd)
	d	= stgArrWords__BYTE_ARR_CTS (amodeToStix cd)
	rs	= amodeToStix rcs
	ra	= stgArrWords__words (amodeToStix rcd)
	rd	= stgArrWords__BYTE_ARR_CTS (amodeToStix rcd)
	a1      = StAssign IntRep ra a
	a2      = StAssign IntRep rs (StPrim IntNegOp [s])
	a3	= StAssign PtrRep rd d
    in
    returnUs (\xs -> a1 : a2 : a3 : xs)
\end{code}

Support for the Gnu GMP multi-precision package.

\begin{code}
-- size (in words) of __MP_INT
mpIntSize = 3 :: Int

mpAlloc, mpSize, mpData :: StixTree -> StixTree
mpAlloc base = StInd IntRep base
mpSize base = StInd IntRep (StIndex IntRep base (StInt 1))
mpData base = StInd PtrRep (StIndex IntRep base (StInt 2))
\end{code}

\begin{code}
toStruct
    :: StixTree
    -> (StixTree, StixTree, StixTree)
    -> (StixTree, StixTree, StixTree)

toStruct str (alloc,size,arr)
  = let
    	f1 = StAssign IntRep (mpAlloc str) alloc
    	f2 = StAssign IntRep (mpSize str) size
    	f3 = StAssign PtrRep (mpData str) arr
    in
    (f1, f2, f3)

scratch1 = StScratchWord 0
scratch2 = StScratchWord mpIntSize
\end{code}