bimaps-0.1.0.2: bijections with multiple implementations.

Safe HaskellNone
LanguageHaskell2010

Data.Bijection.Class

Synopsis

Documentation

data Bimap l r Source #

Bijection between finite sets.

Both data types are strict here.

Constructors

Bimap !l !r 

Instances

(Eq r, Eq l) => Eq (Bimap l r) Source # 

Methods

(==) :: Bimap l r -> Bimap l r -> Bool #

(/=) :: Bimap l r -> Bimap l r -> Bool #

(Read r, Read l) => Read (Bimap l r) Source # 
(Show r, Show l) => Show (Bimap l r) Source # 

Methods

showsPrec :: Int -> Bimap l r -> ShowS #

show :: Bimap l r -> String #

showList :: [Bimap l r] -> ShowS #

Generic (Bimap l r) Source # 

Associated Types

type Rep (Bimap l r) :: * -> * #

Methods

from :: Bimap l r -> Rep (Bimap l r) x #

to :: Rep (Bimap l r) x -> Bimap l r #

(DomCodCnt l r, ToJSON (Dom l), ToJSON (Dom r)) => ToJSON (Bimap l r) Source # 

Methods

toJSON :: Bimap l r -> Value #

toEncoding :: Bimap l r -> Encoding #

toJSONList :: [Bimap l r] -> Value #

toEncodingList :: [Bimap l r] -> Encoding #

(DomCodCnt l r, FromJSON (Dom l), FromJSON (Dom r)) => FromJSON (Bimap l r) Source # 

Methods

parseJSON :: Value -> Parser (Bimap l r) #

parseJSONList :: Value -> Parser [Bimap l r] #

(Binary l, Binary r) => Binary (Bimap l r) Source # 

Methods

put :: Bimap l r -> Put #

get :: Get (Bimap l r) #

putList :: [Bimap l r] -> Put #

(Serialize l, Serialize r) => Serialize (Bimap l r) Source # 

Methods

put :: Putter (Bimap l r) #

get :: Get (Bimap l r) #

(NFData l, NFData r) => NFData (Bimap l r) Source # 

Methods

rnf :: Bimap l r -> () #

type Rep (Bimap l r) Source # 
type Rep (Bimap l r) = D1 (MetaData "Bimap" "Data.Bijection.Class" "bimaps-0.1.0.2-57eg6x1zXWdGzfS2egRGn6" False) (C1 (MetaCons "Bimap" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 l)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 r))))

class DomCod z where Source #

Associated Types

type Dom z :: * Source #

type Cod z :: * Source #

Methods

member :: z -> Dom z -> Bool Source #

lookup :: z -> Dom z -> Maybe (Cod z) Source #

deleteDC :: z -> Dom z -> Maybe (Cod z, z) Source #

insertDC :: z -> (Dom z, Cod z) -> z Source #

toListDC :: z -> [(Dom z, Cod z)] Source #

nullDC :: z -> Bool Source #

emptyDC :: z Source #

sizeDC :: z -> Int Source #

fromListDC :: [(Dom z, Cod z)] -> z Source #

type DomCodCnt l r = (DomCod l, DomCod r, Dom l ~ Cod r, Dom r ~ Cod l) Source #

contL :: Bimap l r -> l Source #

contR :: Bimap l r -> r Source #

memberL :: DomCod l => Bimap l r -> Dom l -> Bool Source #

memberR :: DomCod r => Bimap l r -> Dom r -> Bool Source #

lookupL :: DomCod l => Bimap l r -> Dom l -> Maybe (Cod l) Source #

lookupR :: DomCod r => Bimap l r -> Dom r -> Maybe (Cod r) Source #

empty :: DomCodCnt l r => Bimap l r Source #

null :: DomCod l => Bimap l r -> Bool Source #

size :: DomCod l => Bimap l r -> Int Source #

fromList :: DomCodCnt l r => [(Dom l, Dom r)] -> Bimap l r Source #

Given a list of pairs [(x,y)], turn it into a bimap (x->y, y->x).

toList :: DomCodCnt l r => Bimap l r -> [(Dom l, Dom r)] Source #

insert :: DomCodCnt l r => Bimap l r -> (Dom l, Cod l) -> Bimap l r Source #

deleteByL :: DomCodCnt l r => Bimap l r -> Dom l -> Bimap l r Source #

deleteByR :: DomCodCnt l r => Bimap l r -> Dom r -> Bimap l r Source #

findWithDefaultL :: DomCodCnt l r => Cod l -> Bimap l r -> Dom l -> Cod l Source #

findWithDefaultR :: DomCodCnt l r => Cod r -> Bimap l r -> Dom r -> Cod r Source #