File: Constructible.hs

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 (29 lines) | stat: -rw-r--r-- 1,106 bytes parent folder | download | duplicates (2)
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
{-# LANGUAGE DataKinds, FlexibleInstances, MultiParamTypeClasses,
  UndecidableInstances, KindSignatures, TypeFamilies, TypeOperators #-}
#if !MIN_VERSION_base(4,8,0)
{-# LANGUAGE OverlappingInstances #-}
#endif

-- | `Constructible` types are those for which `new` is
-- defined. Often these are `GObject`s, but it is possible to
-- construct new (zero-initialized) structures and unions too.

module Data.GI.Base.Constructible
    ( Constructible(..)
    ) where

import Control.Monad.IO.Class (MonadIO)

import Data.GI.Base.Attributes (AttrOp, AttrOpTag(..))
import Data.GI.Base.BasicTypes (GObject, ManagedPtr)
import Data.GI.Base.GObject (constructGObject)

-- | Constructible types, i.e. those which can be allocated by `new`.
class Constructible a (tag :: AttrOpTag) where
  -- | Allocate a new instance of the given type, with the given attributes.
  new :: MonadIO m => (ManagedPtr a -> a) -> [AttrOp a tag] -> m a

-- | Default instance, assuming we have a `GObject`.
instance {-# OVERLAPPABLE #-}
    (GObject a, tag ~ 'AttrConstruct) => Constructible a tag where
        new = constructGObject