apart-0.1.1: Get all your structure and rip it apart.

Copyright(C) 2018 Murat Kasimov
LicenseBSD-style (see the file LICENSE)
MaintainerMurat Kasimov <iokasimov.m@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Data.Apart

Description

Get all your structure and rip it apart.

The main idea: if you can describe your data structure via Cofree, with apart you can serialize, persistent or hash a segment of your structure!

A simple introduction to this library can be found here: https://iokasimov.github.io/posts/2018/05/cofree-will-tear-us-apart

Synopsis

Documentation

newtype Apart t raw value Source #

Structure with scattered segments.

Constructors

Apart 

Fields

Instances

Traversable t => Bitraversable (Apart t) Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Apart t a b -> f (Apart t c d) #

Foldable t => Bifoldable (Apart t) Source # 

Methods

bifold :: Monoid m => Apart t m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Apart t a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Apart t a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Apart t a b -> c #

Functor t => Bifunctor (Apart t) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Apart t a c -> Apart t b d #

first :: (a -> b) -> Apart t a c -> Apart t b c #

second :: (b -> c) -> Apart t a b -> Apart t a c #

Functor t => Functor (Apart t raw) Source # 

Methods

fmap :: (a -> b) -> Apart t raw a -> Apart t raw b #

(<$) :: a -> Apart t raw b -> Apart t raw a #

Apply t => Apply (Apart t raw) Source # 

Methods

(<.>) :: Apart t raw (a -> b) -> Apart t raw a -> Apart t raw b

(.>) :: Apart t raw a -> Apart t raw b -> Apart t raw b

(<.) :: Apart t raw a -> Apart t raw b -> Apart t raw a

liftF2 :: (a -> b -> c) -> Apart t raw a -> Apart t raw b -> Apart t raw c

data Shape t raw value Source #

Type that can tell you about aggregate state of your structure.

Constructors

Ready (t value)

Segment of values in memory

Converted raw

Segment of values somewhere else

Instances

Traversable t => Bitraversable (Shape * t) Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Shape * t a b -> f (Shape * t c d) #

Foldable t => Bifoldable (Shape * t) Source # 

Methods

bifold :: Monoid m => Shape * t m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Shape * t a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Shape * t a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Shape * t a b -> c #

Functor t => Bifunctor (Shape * t) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Shape * t a c -> Shape * t b d #

first :: (a -> b) -> Shape * t a c -> Shape * t b c #

second :: (b -> c) -> Shape * t a b -> Shape * t a c #

Functor t => Functor (Shape * t raw) Source # 

Methods

fmap :: (a -> b) -> Shape * t raw a -> Shape * t raw b #

(<$) :: a -> Shape * t raw b -> Shape * t raw a #

Foldable t => Foldable (Shape * t raw) Source # 

Methods

fold :: Monoid m => Shape * t raw m -> m #

foldMap :: Monoid m => (a -> m) -> Shape * t raw a -> m #

foldr :: (a -> b -> b) -> b -> Shape * t raw a -> b #

foldr' :: (a -> b -> b) -> b -> Shape * t raw a -> b #

foldl :: (b -> a -> b) -> b -> Shape * t raw a -> b #

foldl' :: (b -> a -> b) -> b -> Shape * t raw a -> b #

foldr1 :: (a -> a -> a) -> Shape * t raw a -> a #

foldl1 :: (a -> a -> a) -> Shape * t raw a -> a #

toList :: Shape * t raw a -> [a] #

null :: Shape * t raw a -> Bool #

length :: Shape * t raw a -> Int #

elem :: Eq a => a -> Shape * t raw a -> Bool #

maximum :: Ord a => Shape * t raw a -> a #

minimum :: Ord a => Shape * t raw a -> a #

sum :: Num a => Shape * t raw a -> a #

product :: Num a => Shape * t raw a -> a #

Traversable t => Traversable (Shape * t raw) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Shape * t raw a -> f (Shape * t raw b) #

sequenceA :: Applicative f => Shape * t raw (f a) -> f (Shape * t raw a) #

mapM :: Monad m => (a -> m b) -> Shape * t raw a -> m (Shape * t raw b) #

sequence :: Monad m => Shape * t raw (m a) -> m (Shape * t raw a) #

Apply t => Apply (Shape * t raw) Source # 

Methods

(<.>) :: Shape * t raw (a -> b) -> Shape * t raw a -> Shape * t raw b

(.>) :: Shape * t raw a -> Shape * t raw b -> Shape * t raw b

(<.) :: Shape * t raw a -> Shape * t raw b -> Shape * t raw a

liftF2 :: (a -> b -> c) -> Shape * t raw a -> Shape * t raw b -> Shape * t raw c

Alt t => Alt (Shape * t raw) Source # 

Methods

(<!>) :: Shape * t raw a -> Shape * t raw a -> Shape * t raw a

some :: Applicative (Shape * t raw) => Shape * t raw a -> Shape * t raw [a]

many :: Applicative (Shape * t raw) => Shape * t raw a -> Shape * t raw [a]

(Show (t value), Show value, Show raw) => Show (Shape * t raw value) Source # 

Methods

showsPrec :: Int -> Shape * t raw value -> ShowS #

show :: Shape * t raw value -> String #

showList :: [Shape * t raw value] -> ShowS #

type family Segment (structure :: Type -> Type) (value :: Type) :: Type where ... Source #

Equations

Segment (Cofree t) value = t (Cofree t value) 

type family Scattered (structure :: Type -> Type) (value :: Type) (raw :: Type) :: Type where ... Source #

Equations

Scattered (Cofree t) value raw = Apart t raw value 

type Restorer g t raw value = (Traversable t, Applicative g) => raw -> g (Segment (Cofree t) value) Source #

Pull back segment of values to memory.

type Materializer g t raw value = (Traversable t, Applicative g) => Segment (Cofree t) value -> g raw Source #

Put in-memory values to somewhere else.

recover :: (Traversable t, Applicative g) => Restorer g t raw value -> Scattered (Cofree t) value raw -> g (Cofree t value) Source #

Do nothing with in-memory part, pull back all values of structure to memory.

limit :: (Traversable t, Applicative g) => Int -> Materializer g t raw value -> Cofree t value -> g (Scattered (Cofree t) value raw) Source #

Keep only a certain number of elements in memory, do something with the rest.

throughout :: (Traversable t, Monad g) => (value -> g result) -> Restorer g t raw value -> Scattered (Cofree t) value raw -> g (Cofree t result) Source #

Traverse over scattered structure, including with all restored segments.

inmemory :: (Functor t, Alternative t) => Apart t raw value -> Cofree t value Source #