module Foundation.Collection.Collection
( Collection(..)
, NonEmpty
, getNonEmpty
, nonEmpty
, nonEmpty_
, nonEmptyFmap
) where
import Foundation.Internal.Base
import Foundation.Primitive.Types.OffsetSize
import Foundation.Collection.Element
import qualified Data.List
import qualified Foundation.Primitive.Block as BLK
import qualified Foundation.Array.Unboxed as UV
import qualified Foundation.Array.Boxed as BA
import qualified Foundation.String.UTF8 as S
newtype NonEmpty a = NonEmpty { getNonEmpty :: a }
deriving (Show,Eq)
nonEmpty :: Collection c => c -> Maybe (NonEmpty c)
nonEmpty c
| null c = Nothing
| otherwise = Just (NonEmpty c)
nonEmpty_ :: Collection c => c -> NonEmpty c
nonEmpty_ c
| null c = error "nonEmpty_: assumption failed: collection is empty. consider using nonEmpty and adding proper cases"
| otherwise = NonEmpty c
type instance Element (NonEmpty a) = Element a
instance Collection c => IsList (NonEmpty c) where
type Item (NonEmpty c) = Item c
toList = toList . getNonEmpty
fromList = nonEmpty_ . fromList
nonEmptyFmap :: Functor f => (a -> b) -> NonEmpty (f a) -> NonEmpty (f b)
nonEmptyFmap f (NonEmpty l) = NonEmpty (fmap f l)
class (IsList c, Item c ~ Element c) => Collection c where
null :: c -> Bool
length :: c -> CountOf (Element c)
elem :: forall a . (Eq a, a ~ Element c) => Element c -> c -> Bool
elem e col = not $ e `notElem` col
notElem :: forall a . (Eq a, a ~ Element c) => Element c -> c -> Bool
notElem e col = not $ e `elem` col
maximum :: forall a . (Ord a, a ~ Element c) => NonEmpty c -> Element c
minimum :: forall a . (Ord a, a ~ Element c) => NonEmpty c -> Element c
any :: (Element c -> Bool) -> c -> Bool
all :: (Element c -> Bool) -> c -> Bool
instance Collection [a] where
null = Data.List.null
length = CountOf . Data.List.length
elem = Data.List.elem
notElem = Data.List.notElem
minimum = Data.List.minimum . getNonEmpty
maximum = Data.List.maximum . getNonEmpty
any = Data.List.any
all = Data.List.all
instance UV.PrimType ty => Collection (BLK.Block ty) where
null = (==) 0 . BLK.length
length = BLK.length
elem = BLK.elem
minimum = Data.List.minimum . toList . getNonEmpty
maximum = Data.List.maximum . toList . getNonEmpty
all = BLK.all
any = BLK.any
instance UV.PrimType ty => Collection (UV.UArray ty) where
null = UV.null
length = UV.length
elem = UV.elem
minimum = Data.List.minimum . toList . getNonEmpty
maximum = Data.List.maximum . toList . getNonEmpty
all p = Data.List.all p . toList
any p = Data.List.any p . toList
instance Collection (BA.Array ty) where
null = BA.null
length = BA.length
elem = BA.elem
minimum = Data.List.minimum . toList . getNonEmpty
maximum = Data.List.maximum . toList . getNonEmpty
all p = Data.List.all p . toList
any p = Data.List.any p . toList
instance Collection S.String where
null = S.null
length = S.length
elem = S.elem
minimum = Data.List.minimum . toList . getNonEmpty
maximum = Data.List.maximum . toList . getNonEmpty
all p = Data.List.all p . toList
any p = Data.List.any p . toList
instance Collection c => Collection (NonEmpty c) where
null _ = False
length = length . getNonEmpty
elem e = elem e . getNonEmpty
maximum = maximum . getNonEmpty
minimum = minimum . getNonEmpty
all p = all p . getNonEmpty
any p = any p . getNonEmpty