File: SlowFunctions.hs

package info (click to toggle)
ghc 9.6.6-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, trixie
  • size: 158,216 kB
  • sloc: haskell: 648,228; ansic: 81,656; cpp: 11,808; javascript: 8,444; sh: 5,831; fortran: 3,527; python: 3,277; asm: 2,523; makefile: 2,298; yacc: 1,570; lisp: 532; xml: 196; perl: 145; csh: 2
file content (39 lines) | stat: -rw-r--r-- 1,278 bytes parent folder | download | duplicates (10)
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
{-# LANGUAGE BangPatterns #-}
module Tests.SlowFunctions
    (
      indices
    , splitOn
    ) where

import qualified Data.Text as T
import Data.Text.Internal (Text(..))
import Data.Text.Unsafe (iter_, unsafeHead, unsafeTail)

indices :: T.Text              -- ^ Substring to search for (@needle@)
        -> T.Text              -- ^ Text to search in (@haystack@)
        -> [Int]
indices needle@(Text _narr _noff nlen) haystack@(Text harr hoff hlen)
    | T.null needle = []
    | otherwise     = scan 0
  where
    scan i | i >= hlen = []
           | needle `T.isPrefixOf` t = i : scan (i+nlen)
           | otherwise = scan (i+d)
           where t = Text harr (hoff+i) (hlen-i)
                 d = iter_ haystack i

splitOn :: T.Text               -- ^ Text to split on
        -> T.Text               -- ^ Input text
        -> [T.Text]
splitOn pat src0
    | T.null pat  = error "splitOn: empty"
    | l == 1      = T.split (== (unsafeHead pat)) src0
    | otherwise   = go src0
  where
    l      = T.length pat
    go src = search 0 src
      where
        search !n !s
            | T.null s             = [src]      -- not found
            | pat `T.isPrefixOf` s = T.take n src : go (T.drop l s)
            | otherwise            = search (n+1) (unsafeTail s)