File: Enumerator.hsc

package info (click to toggle)
haskell-text-icu 0.8.0.5-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 536 kB
  • sloc: haskell: 1,210; ansic: 1,147; makefile: 4
file content (61 lines) | stat: -rw-r--r-- 1,934 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
{-# LANGUAGE EmptyDataDecls, BangPatterns, ForeignFunctionInterface, RecordWildCards #-}
-- |
-- Module      : Data.Text.ICU.Calendar
-- Copyright   : (c) 2021 Torsten Kemps-Benedix
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : GHC
--
-- Calendar functions implemented as bindings to
-- the International Components for Unicode (ICU) libraries.

module Data.Text.ICU.Enumerator
    (next, toList, createEnumerator, Enumerator, UEnumerator,
    ) where

#include <unicode/uenum.h>

import Data.Int (Int32)
import Data.Text (Text)
import Data.Text.ICU.Error.Internal (UErrorCode, handleError)
import Data.Text.ICU.Internal (UChar, newICUPtr, fromUCharPtr)
import Foreign.ForeignPtr (withForeignPtr, ForeignPtr)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr (FunPtr, Ptr, nullPtr)
import Foreign.Storable (peek)
import Prelude hiding (last)

data UEnumerator

newtype Enumerator = Enumerator {enumeratorToForeignPtr :: ForeignPtr UEnumerator}

createEnumerator :: IO (Ptr UEnumerator) -> IO Enumerator
createEnumerator = newICUPtr Enumerator uenum_close

next :: Enumerator -> IO (Maybe Text)
next enum = withForeignPtr (enumeratorToForeignPtr enum) $ \enumPtr ->
  alloca $ \lenPtr -> do
    textPtr <- handleError $ uenum_unext enumPtr lenPtr
    if textPtr == nullPtr
      then pure Nothing
      else do
          n <- peek lenPtr
          t <- fromUCharPtr textPtr (fromIntegral n)
          pure $ Just t

toList :: Enumerator -> IO [Text]
toList enum = reverse <$> go []
  where
    go l = do
      mx <- next enum
      case mx of
        Nothing -> pure l
        Just x -> go (x:l)

foreign import ccall unsafe "hs_text_icu.h &__hs_uenum_close" uenum_close
    :: FunPtr (Ptr UEnumerator -> IO ())
foreign import ccall unsafe "hs_text_icu.h __hs_uenum_unext" uenum_unext
    :: Ptr UEnumerator -> Ptr Int32 -> Ptr UErrorCode
    -> IO (Ptr UChar)