hgeometry-combinatorial-0.12.0.2: Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Ext.Multi

Description

A pair-like data type to represent a core type that has extra information as well.

Documentation

data family core :+ (extras :: [*]) :: * infixr 1 Source #

Instances

Instances details
Eq core => Eq (core :+ ('[] :: [Type])) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

(==) :: (core :+ '[]) -> (core :+ '[]) -> Bool #

(/=) :: (core :+ '[]) -> (core :+ '[]) -> Bool #

Ord core => Ord (core :+ ('[] :: [Type])) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

compare :: (core :+ '[]) -> (core :+ '[]) -> Ordering #

(<) :: (core :+ '[]) -> (core :+ '[]) -> Bool #

(<=) :: (core :+ '[]) -> (core :+ '[]) -> Bool #

(>) :: (core :+ '[]) -> (core :+ '[]) -> Bool #

(>=) :: (core :+ '[]) -> (core :+ '[]) -> Bool #

max :: (core :+ '[]) -> (core :+ '[]) -> core :+ '[] #

min :: (core :+ '[]) -> (core :+ '[]) -> core :+ '[] #

Show core => Show (core :+ ('[] :: [Type])) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

showsPrec :: Int -> (core :+ '[]) -> ShowS #

show :: (core :+ '[]) -> String #

showList :: [core :+ '[]] -> ShowS #

Generic (core :+ ('[] :: [Type])) Source # 
Instance details

Defined in Data.Ext.Multi

Associated Types

type Rep (core :+ '[]) :: Type -> Type #

Methods

from :: (core :+ '[]) -> Rep (core :+ '[]) x #

to :: Rep (core :+ '[]) x -> core :+ '[] #

Arbitrary core => Arbitrary (core :+ ('[] :: [Type])) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

arbitrary :: Gen (core :+ '[]) #

shrink :: (core :+ '[]) -> [core :+ '[]] #

NFData core => NFData (core :+ ('[] :: [Type])) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

rnf :: (core :+ '[]) -> () #

newtype core :+ ('[] :: [Type]) Source # 
Instance details

Defined in Data.Ext.Multi

newtype core :+ ('[] :: [Type]) = Only core
data core :+ (t ': ts) Source # 
Instance details

Defined in Data.Ext.Multi

data core :+ (t ': ts) = WithExtra !core (HList (t ': ts))
type Rep (core :+ ('[] :: [Type])) Source # 
Instance details

Defined in Data.Ext.Multi

type Rep (core :+ ('[] :: [Type])) = D1 ('MetaData ":+" "Data.Ext.Multi" "hgeometry-combinatorial-0.12.0.2-BPOszceZMWb3Na6sqXbM08" 'True) (C1 ('MetaCons "Only" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 core)))

pattern (:+) :: c -> HList (e ': extras) -> c :+ (e ': extras) infixr 1 Source #

ext :: c -> c :+ '[] Source #

class HasCore extras where Source #

Methods

core :: Lens (core :+ extras) (core' :+ extras) core core' Source #

Instances

Instances details
HasCore ('[] :: [Type]) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

core :: Lens (core :+ '[]) (core' :+ '[]) core core' Source #

HasCore (t ': ts) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

core :: Lens (core :+ (t ': ts)) (core' :+ (t ': ts)) core core' Source #

class HasExtras extras extras' where Source #

Methods

extra :: Lens (core :+ extras) (core :+ extras') (HList extras) (HList extras') Source #

Instances

Instances details
HasExtras ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

extra :: Lens (core :+ '[]) (core :+ '[]) (HList '[]) (HList '[]) Source #

HasExtras ('[] :: [Type]) (t ': ts) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

extra :: Lens (core :+ '[]) (core :+ (t ': ts)) (HList '[]) (HList (t ': ts)) Source #

HasExtras (t ': ts) ('[] :: [Type]) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

extra :: Lens (core :+ (t ': ts)) (core :+ '[]) (HList (t ': ts)) (HList '[]) Source #

HasExtras (t ': ts) (a ': as) Source # 
Instance details

Defined in Data.Ext.Multi

Methods

extra :: Lens (core :+ (t ': ts)) (core :+ (a ': as)) (HList (t ': ts)) (HList (a ': as)) Source #