File: UVect.hs

package info (click to toggle)
haskell-basement 0.0.16-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,048 kB
  • sloc: haskell: 11,336; ansic: 63; makefile: 5
file content (159 lines) | stat: -rw-r--r-- 5,234 bytes parent folder | download | duplicates (4)
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
{-# LANGUAGE AllowAmbiguousTypes        #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE TypeOperators              #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ConstraintKinds            #-}
module Basement.Sized.UVect
    ( UVect
    , MUVect
    , unUVect
    , toUVect
    , empty
    , singleton
    , replicate
    , thaw
    , freeze
    , index
    , map
    , foldl'
    , foldr
    , cons
    , snoc
    , elem
    , sub
    , uncons
    , unsnoc
    , splitAt
    , all
    , any
    , find
    , reverse
    , sortBy
    , intersperse
    ) where

import           Basement.Compat.Base
import           Basement.Nat
import           Basement.NormalForm
import           Basement.Types.OffsetSize
import           Basement.Monad
import           Basement.PrimType (PrimType)
import qualified Basement.UArray as A
import qualified Basement.UArray.Mutable as A hiding (sub)
import           Data.Proxy

newtype UVect (n :: Nat) a = UVect { unUVect :: A.UArray a } deriving (NormalForm, Eq, Show)
newtype MUVect (n :: Nat) ty st = MUVect { unMUVect :: A.MUArray ty st }

toUVect :: forall n ty . (PrimType ty, KnownNat n, Countable ty n) => A.UArray ty -> Maybe (UVect n ty)
toUVect b
    | expected == A.length b = Just (UVect b)
    | otherwise              = Nothing
  where
    expected = toCount @n

empty :: PrimType ty => UVect 0 ty
empty = UVect mempty

singleton :: PrimType ty => ty -> UVect 1 ty
singleton a = UVect (A.singleton a)

create :: forall ty (n :: Nat) . (PrimType ty, Countable ty n, KnownNat n) => (Offset ty -> ty) -> UVect n ty
create f = UVect $ A.create sz f
  where
    sz = natValCountOf (Proxy :: Proxy n)

replicate :: forall n ty . (KnownNat n, Countable ty n, PrimType ty) => ty -> UVect n ty
replicate a = UVect (A.replicate (toCount @n) a)

thaw :: (KnownNat n, PrimMonad prim, PrimType ty) => UVect n ty -> prim (MUVect n ty (PrimState prim))
thaw b = MUVect <$> A.thaw (unUVect b)

freeze ::  (PrimMonad prim, PrimType ty, Countable ty n) => MUVect n ty (PrimState prim) -> prim (UVect n ty)
freeze b = UVect <$> A.freeze (unMUVect b)

write :: (PrimMonad prim, PrimType ty) => MUVect n ty (PrimState prim) -> Offset ty -> ty -> prim ()
write (MUVect ma) ofs v = A.write ma ofs v

read :: (PrimMonad prim, PrimType ty) => MUVect n ty (PrimState prim) -> Offset ty -> prim ty
read (MUVect ma) ofs = A.read ma ofs

indexStatic :: forall i n ty . (KnownNat i, CmpNat i n ~ 'LT, PrimType ty, Offsetable ty i) => UVect n ty -> ty
indexStatic b = A.unsafeIndex (unUVect b) (toOffset @i)

index :: forall i n ty . PrimType ty => UVect n ty -> Offset ty -> ty
index b ofs = A.index (unUVect b) ofs

map :: (PrimType a, PrimType b) => (a -> b) -> UVect n a -> UVect n b
map f b = UVect (A.map f (unUVect b))

foldl' :: PrimType ty => (a -> ty -> a) -> a -> UVect n ty -> a
foldl' f acc b = A.foldl' f acc (unUVect b)

foldr :: PrimType ty => (ty -> a -> a) -> a -> UVect n ty -> a
foldr f acc b = A.foldr f acc (unUVect b)

cons :: PrimType ty => ty -> UVect n ty -> UVect (n+1) ty
cons e = UVect . A.cons e . unUVect

snoc :: PrimType ty => UVect n ty -> ty -> UVect (n+1) ty
snoc b = UVect . A.snoc (unUVect b)

sub :: forall i j n ty
     . ( (i <=? n) ~ 'True
       , (j <=? n) ~ 'True
       , (i <=? j) ~ 'True
       , PrimType ty
       , KnownNat i
       , KnownNat j
       , Offsetable ty i
       , Offsetable ty j )
    => UVect n ty
    -> UVect (j-i) ty
sub block = UVect (A.sub (unUVect block) (toOffset @i) (toOffset @j))

uncons :: forall n ty . (CmpNat 0 n ~ 'LT, PrimType ty, KnownNat n, Offsetable ty n)
       => UVect n ty
       -> (ty, UVect (n-1) ty)
uncons b = (indexStatic @0 b, UVect (A.sub (unUVect b) 1 (toOffset @n)))

unsnoc :: forall n ty . (CmpNat 0 n ~ 'LT, KnownNat n, PrimType ty, Offsetable ty n)
       => UVect n ty
       -> (UVect (n-1) ty, ty)
unsnoc b =
    ( UVect (A.sub (unUVect b) 0 (toOffset @n `offsetSub` 1))
    , A.unsafeIndex (unUVect b) (toOffset @n `offsetSub` 1))

splitAt :: forall i n ty . (CmpNat i n ~ 'LT, PrimType ty, KnownNat i, Countable ty i) => UVect n ty -> (UVect i ty, UVect (n-i) ty)
splitAt b =
    let (left, right) = A.splitAt (toCount @i) (unUVect b)
     in (UVect left, UVect right)

elem :: PrimType ty => ty -> UVect n ty -> Bool
elem e b = A.elem e (unUVect b)

all :: PrimType ty => (ty -> Bool) -> UVect n ty -> Bool
all p b = A.all p (unUVect b)

any :: PrimType ty => (ty -> Bool) -> UVect n ty -> Bool
any p b = A.any p (unUVect b)

find :: PrimType ty => (ty -> Bool) -> UVect n ty -> Maybe ty
find p b = A.find p (unUVect b)

reverse :: PrimType ty => UVect n ty -> UVect n ty
reverse = UVect . A.reverse . unUVect

sortBy :: PrimType ty => (ty -> ty -> Ordering) -> UVect n ty -> UVect n ty
sortBy f b = UVect (A.sortBy f (unUVect b))

intersperse :: (CmpNat n 1 ~ 'GT, PrimType ty) => ty -> UVect n ty -> UVect (n+n-1) ty
intersperse sep b = UVect (A.intersperse sep (unUVect b))

toCount :: forall n ty . (KnownNat n, Countable ty n) => CountOf ty
toCount = natValCountOf (Proxy @n)

toOffset :: forall n ty . (KnownNat n, Offsetable ty n) => Offset ty
toOffset = natValOffset (Proxy @n)