File: List.hs

package info (click to toggle)
haskell-foundation 0.0.30-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 932 kB
  • sloc: haskell: 9,124; ansic: 570; makefile: 7
file content (41 lines) | stat: -rw-r--r-- 1,249 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
{-# LANGUAGE NoImplicitPrelude #-}

module Test.Data.List
    ( generateListOfElement
    , generateListOfElementMaxN
    , generateNonEmptyListOfElement
    , RandomList(..)
    ) where

import Foundation
import Foundation.Collection (nonEmpty_, NonEmpty)
import Foundation.Check
import Foundation.Monad

import Basement.From (from)
import Basement.Cast (cast)

-- | convenient function to replicate thegiven Generator of `e` a randomly
-- choosen amount of time.
generateListOfElement :: Gen e -> Gen [e]
generateListOfElement = generateListOfElementMaxN 100

-- | convenient function to generate up to a certain amount of time the given
-- generator.
generateListOfElementMaxN :: CountOf e -> Gen e -> Gen [e]
generateListOfElementMaxN n e = replicateBetween 0 (from n) e

generateNonEmptyListOfElement :: CountOf e -> Gen e -> Gen (NonEmpty [e])
generateNonEmptyListOfElement n e = nonEmpty_ <$> replicateBetween 1 (from n) e

data RandomList = RandomList [Int]
    deriving (Show,Eq)

instance Arbitrary RandomList where
    arbitrary = RandomList <$> replicateBetween 100 400 (cast <$> between (0,8))

replicateBetween n1 n2 f =
    between (n1, n2) >>= \n -> replicateM (CountOf (toInt n)) f
  where
    toInt :: Word -> Int
    toInt = cast