File: BasicTypes.hsc

package info (click to toggle)
haskell-haskell-gi-base 0.26.8-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 408 kB
  • sloc: haskell: 1,604; ansic: 324; makefile: 5
file content (223 lines) | stat: -rw-r--r-- 8,209 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
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
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
{-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances,
  DeriveDataTypeable, TypeFamilies, ScopedTypeVariables,
  MultiParamTypeClasses, DataKinds, TypeOperators, UndecidableInstances,
  AllowAmbiguousTypes #-}

-- | Basic types used in the bindings.
module Data.GI.Base.BasicTypes
    (
     -- * Memory management
      ManagedPtr(..)
    , ManagedPtrNewtype(..)
    , BoxedPtr(..)
    , CallocPtr(..)
    , UnexpectedNullPointerReturn(..)

    -- * Basic GLib \/ GObject types
    , TypedObject(..)
    , GObject
    , GType(..)
    , CGType
    , gtypeName
    , GVariant(..)
    , GBoxed
    , BoxedEnum
    , BoxedFlags
    , GParamSpec(..)
    , noGParamSpec

    , GArray(..)
    , GPtrArray(..)
    , GByteArray(..)
    , GHashTable(..)
    , GList(..)
    , g_list_free
    , GSList(..)
    , g_slist_free

    , IsGFlag

    , PtrWrapped(..)
    , GDestroyNotify

    , GHashFunc
    , GEqualFunc
    ) where

import Control.Exception (Exception)

import Data.Coerce (coerce, Coercible)
import Data.IORef (IORef)
import qualified Data.Text as T
import Data.Typeable (Typeable)
import Data.Int
import Data.Word

import Foreign.C (CString, peekCString)
import Foreign.Ptr (Ptr, FunPtr)
import Foreign.ForeignPtr (ForeignPtr)

import {-# SOURCE #-} Data.GI.Base.Overloading (HasParentTypes)
import Data.GI.Base.CallStack (CallStack)

#include <glib-object.h>

-- | Thin wrapper over `ForeignPtr`, supporting the extra notion of
-- `disowning`, that is, not running the finalizers associated with
-- the foreign ptr.
data ManagedPtr a = ManagedPtr {
      managedForeignPtr :: ForeignPtr a
    , managedPtrAllocCallStack :: Maybe CallStack
    -- ^ `CallStack` for the call that created the pointer.
    , managedPtrIsDisowned :: IORef (Maybe CallStack)
    -- ^ When disowned, the `CallStack` for the disowning call.
    }

-- | Two 'ManagedPtr's are equal if they wrap the same underlying
-- C 'Ptr'.
instance Eq (ManagedPtr a) where
  a == b = managedForeignPtr a == managedForeignPtr b

-- | A constraint ensuring that the given type is a newtype over a
-- `ManagedPtr`.
class Coercible a (ManagedPtr ()) => ManagedPtrNewtype a where
  toManagedPtr :: a -> ManagedPtr a

-- | A default instance for `IsManagedPtr` for newtypes over `ManagedPtr`.
instance {-# OVERLAPPABLE #-} Coercible a (ManagedPtr ()) => ManagedPtrNewtype a where
  toManagedPtr = coerce
-- Notice that the Coercible here above to ManagedPtr (), instead of
-- "ManagedPtr a", which would be the most natural thing. Both are
-- representationally equivalent, so this is not a big deal. This is
-- to work around a problem in ghc 7.10:
-- https://ghc.haskell.org/trac/ghc/ticket/10715
--
-- Additionally, a simpler approach would be to simply do
--
-- > type IsManagedPtr a = Coercible a (ManagedPtr ())
--
-- but this requires the constructor of the datatype to be in scope,
-- which is cumbersome (for instance, one often wants to call `castTo`
-- on the results of `Gtk.builderGetObject`, which is a `GObject`,
-- whose constructor is not necessarily in scope when using `GI.Gtk`).
--
-- When we make the bindings we will always add explicit instances,
-- which cannot be hidden, avoiding the issue. We keep the default
-- instance for convenience when writing new object types.

-- | Pointers to chunks of memory which we know how to copy and
-- release.
class ManagedPtrNewtype a => BoxedPtr a where
  -- | Make a copy of the given `BoxedPtr`.
  boxedPtrCopy   :: a -> IO a
  -- | A pointer to a function for freeing the given pointer.
  boxedPtrFree   :: a -> IO ()

-- | A ptr to a memory block which we know how to allocate and fill
-- with zero.
class BoxedPtr a => CallocPtr a where
  -- | Allocate a zero-initialized block of memory for the given type.
  boxedPtrCalloc :: IO (Ptr a)

-- | A wrapped object that has an associated GLib type. This does not
-- necessarily descend from `GObject`, that constraint is implemented
-- by `GObject` below.
class HasParentTypes a => TypedObject a where
  -- | The `GType` for this object.
  glibType :: IO GType

-- | Chunks of memory whose allocation/deallocation info has been
-- registered with the GLib type system.
class (ManagedPtrNewtype a, TypedObject a) => GBoxed a

-- | A wrapped `GObject`, or any other type that descends from it.
class (ManagedPtrNewtype a, TypedObject a) => GObject a

-- | Enums with an associated `GType`.
class TypedObject a => BoxedEnum a

-- | Flags with an associated `GType`.
class TypedObject a => BoxedFlags a

-- | A type identifier in the GLib type system. This is the low-level
-- type associated with the representation in memory, when using this
-- on the Haskell side use `GType` below.
type CGType = #type GType

-- | A newtype for use on the Haskell side.
newtype GType = GType {gtypeToCGType :: CGType}
  deriving (Eq, Show)

foreign import ccall "g_type_name" g_type_name :: GType -> IO CString

-- | Get the name assigned to the given `GType`.
gtypeName :: GType -> IO String
gtypeName gtype = g_type_name gtype >>= peekCString

-- | A common omission in the introspection data is missing (nullable)
-- annotations for return types, when they clearly are nullable. (A
-- common idiom is "Returns: valid value, or %NULL if something went
-- wrong.")
--
-- Haskell wrappers will raise this exception if the return value is
-- an unexpected `Foreign.Ptr.nullPtr`.
data UnexpectedNullPointerReturn =
    UnexpectedNullPointerReturn { nullPtrErrorMsg :: T.Text }
                                deriving (Typeable)

instance Show UnexpectedNullPointerReturn where
  show r = T.unpack (nullPtrErrorMsg r)

instance Exception UnexpectedNullPointerReturn

-- | A <https://docs.gtk.org/glib/struct.Variant.html GVariant>. See "Data.GI.Base.GVariant" for further methods.
newtype GVariant = GVariant (ManagedPtr GVariant)

-- | A <https://docs.gtk.org/gobject/class.ParamSpec.html GParamSpec>. See "Data.GI.Base.GParamSpec" for further methods.
newtype GParamSpec = GParamSpec (ManagedPtr GParamSpec)

-- | A convenient synonym for @Nothing :: Maybe GParamSpec@.
noGParamSpec :: Maybe GParamSpec
noGParamSpec = Nothing

-- | An enum usable as a flag for a function.
class Enum a => IsGFlag a

-- | A <https://docs.gtk.org/glib/struct.Array.html GArray>. Marshalling for this type is done in "Data.GI.Base.BasicConversions", it is mapped to a list on the Haskell side.
data GArray a = GArray (Ptr (GArray a))

-- | A <https://docs.gtk.org/glib/struct.PtrArray.html GPtrArray>. Marshalling for this type is done in "Data.GI.Base.BasicConversions", it is mapped to a list on the Haskell side.
data GPtrArray a = GPtrArray (Ptr (GPtrArray a))

-- | A <https://docs.gtk.org/glib/struct.ByteArray.html GByteArray>. Marshalling for this type is done in "Data.GI.Base.BasicConversions", it is packed to a 'Data.ByteString.ByteString' on the Haskell side.
data GByteArray = GByteArray (Ptr GByteArray)

-- | A <https://docs.gtk.org/glib/struct.HashTable.html GHashTable>. It is mapped to a 'Data.Map.Map' on the Haskell side.
data GHashTable a b = GHashTable (Ptr (GHashTable a b))

-- | A <https://docs.gtk.org/glib/struct.List.html GList>, mapped to a list on the Haskell side. Marshalling is done in "Data.GI.Base.BasicConversions".
data GList a = GList (Ptr (GList a))

-- | A <https://docs.gtk.org/glib/struct.SList.html GSList>, mapped to a list on the Haskell side. Marshalling is done in "Data.GI.Base.BasicConversions".
data GSList a = GSList (Ptr (GSList a))

-- | Some APIs, such as `GHashTable`, pass around scalar types
-- wrapped into a pointer. We encode such a type as follows.
newtype PtrWrapped a = PtrWrapped {unwrapPtr :: Ptr a}

-- | Destroy the memory pointed to by a given pointer type.
type GDestroyNotify ptr = FunPtr (ptr -> IO ())

-- | Free the given 'GList'.
foreign import ccall "g_list_free" g_list_free ::
    Ptr (GList a) -> IO ()

-- | Free the given 'GSList'.
foreign import ccall "g_slist_free" g_slist_free ::
    Ptr (GSList a) -> IO ()

-- | A pointer to a hashing function on the C side.
type GHashFunc a = FunPtr (PtrWrapped a -> IO #{type guint})

-- | A pointer to an equality checking function on the C side.
type GEqualFunc a = FunPtr (PtrWrapped a -> PtrWrapped a -> IO #{type gboolean})