File: Unfold.hs

package info (click to toggle)
haskell-unicode-data 0.4.0.1-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 5,024 kB
  • sloc: haskell: 26,394; makefile: 3
file content (64 lines) | stat: -rw-r--r-- 1,706 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
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
{-# LANGUAGE CPP                       #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE LambdaCase                #-}

-- |
-- Module      : Unicode.Internal.Unfold
-- Copyright   : (c) 2022 Composewell Technologies and Contributors
-- License     : BSD-3-Clause
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--
-- @since 0.3.1
--

module Unicode.Internal.Unfold
    ( Unfold(..)
    , Step(..)
    , toList
    ) where

-- | An @Unfold a b@ is a generator of a stream of values of type @b@ from a
-- seed of type @a@.
--
-- @since 0.3.1
#if MIN_VERSION_base(4,12,0)
data Unfold a b = forall s. Unfold
    (s -> Step s b)
    -- ^ /Step/ function: compute the next step from the current one.
    (a -> Step s b)
    -- ^ /Inject/ function: initialize the state with a seed value.
#else
data Unfold a b =
    -- | @Unfold step inject@
    forall s. Unfold (s -> Step s b) (a -> Step s b)
#endif

-- | A stream is a succession of 'Step's.
--
-- @since 0.3.1
data Step s a
    = Yield !a !s
    -- ^ Produces a single value and the next state of the stream.
    | Stop
    -- ^ Indicates there are no more values in the stream.

instance Functor (Step s) where
    {-# INLINE fmap #-}
    fmap f (Yield x s) = Yield (f x) s
    fmap _ Stop        = Stop

-- | Convert an 'Unfold a a' to a list [a], if the resulting list is empty the
-- seed is used as a default output.
--
{-# INLINE toList #-}
toList :: Unfold a a -> a -> [a]
toList (Unfold step inject) input =
    case inject input of
        Stop -> [input]
        Yield b s -> b : go (step s)
    where
    go = \case
        Yield b s -> let !s' = step s in b : go s'
        Stop      -> []