Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
GHC
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Container Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
alexbiehl-gc
GHC
Commits
9c5d0e22
Commit
9c5d0e22
authored
26 years ago
by
sof
Browse files
Options
Downloads
Patches
Plain Diff
[project @ 1998-08-14 12:57:27 by sof]
Remove ForeignObj unpacking functions; doesn't belong here
parent
d0e4be14
No related branches found
No related tags found
No related merge requests found
Changes
1
Hide whitespace changes
Inline
Side-by-side
Showing
1 changed file
ghc/lib/std/PrelForeign.lhs
+17
-55
17 additions, 55 deletions
ghc/lib/std/PrelForeign.lhs
with
17 additions
and
55 deletions
ghc/lib/std/PrelForeign.lhs
+
17
−
55
View file @
9c5d0e22
...
@@ -11,15 +11,9 @@ module PrelForeign (
...
@@ -11,15 +11,9 @@ module PrelForeign (
module PrelForeign,
module PrelForeign,
#ifndef __PARALLEL_HASKELL__
#ifndef __PARALLEL_HASKELL__
ForeignObj(..),
ForeignObj(..),
makeForeignObj,
#endif
#endif
Word(..),
StateAndForeignObj#(..)
#ifndef __PARALLEL_HASKELL__
unpackCStringFO, -- :: ForeignObj -> [Char]
unpackNBytesFO, -- :: ForeignObj -> Int -> [Char]
unpackCStringFO#, -- :: ForeignObj# -> [Char]
unpackNBytesFO# -- :: ForeignObj# -> Int# -> [Char]
#endif
) where
) where
import PrelIOBase
import PrelIOBase
...
@@ -39,19 +33,22 @@ import PrelGHC
...
@@ -39,19 +33,22 @@ import PrelGHC
\begin{code}
\begin{code}
#ifndef __PARALLEL_HASKELL__
#ifndef __PARALLEL_HASKELL__
instance CCallable ForeignObj
--
instance CCallable ForeignObj
instance CCallable ForeignObj#
--
instance CCallable ForeignObj#
eqForeignObj :: ForeignObj -> ForeignObj -> Bool
eqForeignObj :: ForeignObj -> ForeignObj -> Bool
makeForeignObj :: Addr -> Addr -> IO ForeignObj
--
makeForeignObj :: Addr -> Addr -> IO ForeignObj
writeForeignObj :: ForeignObj -> Addr -> IO ()
writeForeignObj :: ForeignObj -> Addr -> IO ()
{- derived op - attaching a free() finaliser to a malloc() allocated reference. -}
{- derived op - attaching a free() finaliser to a malloc() allocated reference. -}
makeMallocPtr :: Addr -> IO ForeignObj
makeMallocPtr :: Addr -> IO ForeignObj
{-
--makeForeignObj :: Addr -> Addr -> IO ForeignObj
makeForeignObj (A# obj) (A# finaliser) = IO ( \ s# ->
makeForeignObj (A# obj) (A# finaliser) = IO ( \ s# ->
case makeForeignObj# obj finaliser s# of
case makeForeignObj# obj finaliser s# of
StateAndForeignObj# s1# fo# -> IOok s1# (ForeignObj fo#))
StateAndForeignObj# s1# fo# -> IOok s1# (ForeignObj fo#))
-}
writeForeignObj (ForeignObj fo#) (A# datum#) = IO ( \ s# ->
writeForeignObj (ForeignObj fo#) (A# datum#) = IO ( \ s# ->
case writeForeignObj# fo# datum# s# of { s1# -> IOok s1# () } )
case writeForeignObj# fo# datum# s# of { s1# -> IOok s1# () } )
...
@@ -101,6 +98,14 @@ deRefStablePtr (StablePtr sp#) = IO $ \ rw1# ->
...
@@ -101,6 +98,14 @@ deRefStablePtr (StablePtr sp#) = IO $ \ rw1# ->
freeStablePtr sp = _ccall_ freeStablePointer sp
freeStablePtr sp = _ccall_ freeStablePointer sp
eqStablePtr :: StablePtr a -> StablePtr b -> Bool
eqStablePtr s1 s2
= unsafePerformIO (_ccall_ eqStablePtr s1 s2) /= (0::Int)
instance Eq (StablePtr a) where
p == q = eqStablePtr p q
p /= q = not (eqStablePtr p q)
#endif /* !__PARALLEL_HASKELL__ */
#endif /* !__PARALLEL_HASKELL__ */
\end{code}
\end{code}
...
@@ -114,48 +119,5 @@ freeStablePtr sp = _ccall_ freeStablePointer sp
...
@@ -114,48 +119,5 @@ freeStablePtr sp = _ccall_ freeStablePointer sp
#ifndef __PARALLEL_HASKELL__
#ifndef __PARALLEL_HASKELL__
data StateAndStablePtr# s a = StateAndStablePtr# (State# s) (StablePtr# a)
data StateAndStablePtr# s a = StateAndStablePtr# (State# s) (StablePtr# a)
#endif
#endif
data StateAndForeignObj# s = StateAndForeignObj# (State# s) ForeignObj#
--data StateAndForeignObj# s = StateAndForeignObj# (State# s) ForeignObj#
\end{code}
%*********************************************************
%* *
\subsection{Unpacking Foreigns}
%* *
%*********************************************************
Primitives for converting Foreigns pointing to external
sequence of bytes into a list of @Char@s (a renamed version
of the code above).
\begin{code}
#ifndef __PARALLEL_HASKELL__
unpackCStringFO :: ForeignObj -> [Char]
unpackCStringFO (ForeignObj fo#) = unpackCStringFO# fo#
unpackCStringFO# :: ForeignObj# -> [Char]
unpackCStringFO# fo {- ptr. to NUL terminated string-}
= unpack 0#
where
unpack nh
| ch `eqChar#` '\0'# = []
| otherwise = C# ch : unpack (nh +# 1#)
where
ch = indexCharOffForeignObj# fo nh
unpackNBytesFO :: ForeignObj -> Int -> [Char]
unpackNBytesFO (ForeignObj fo) (I# l) = unpackNBytesFO# fo l
unpackNBytesFO# :: ForeignObj# -> Int# -> [Char]
-- This one is called by the compiler to unpack literal strings with NULs in them; rare.
unpackNBytesFO# fo len
= unpack 0#
where
unpack i
| i >=# len = []
| otherwise = C# ch : unpack (i +# 1#)
where
ch = indexCharOffForeignObj# fo i
#endif
\end{code}
\end{code}
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment