cybus-0.3.0.0: multi-dimensional arrays
Copyright(c) Grant Weyburne 2022
LicenseBSD-3
Safe HaskellNone
LanguageHaskell2010

Cybus.Fin

Description

used for single indexes into a Mat or FinMat

Synopsis

Documentation

data Fin n Source #

definition of the Finite type

Instances

Instances details
Generic1 Fin Source # 
Instance details

Defined in Cybus.Fin

Associated Types

type Rep1 Fin :: k -> Type #

Methods

from1 :: forall (a :: k). Fin a -> Rep1 Fin a #

to1 :: forall (a :: k). Rep1 Fin a -> Fin a #

PosC n => Bounded (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

minBound :: Fin n #

maxBound :: Fin n #

PosC n => Enum (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

succ :: Fin n -> Fin n #

pred :: Fin n -> Fin n #

toEnum :: Int -> Fin n #

fromEnum :: Fin n -> Int #

enumFrom :: Fin n -> [Fin n] #

enumFromThen :: Fin n -> Fin n -> [Fin n] #

enumFromTo :: Fin n -> Fin n -> [Fin n] #

enumFromThenTo :: Fin n -> Fin n -> Fin n -> [Fin n] #

Eq (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

(==) :: Fin n -> Fin n -> Bool #

(/=) :: Fin n -> Fin n -> Bool #

PosC n => Num (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

(+) :: Fin n -> Fin n -> Fin n #

(-) :: Fin n -> Fin n -> Fin n #

(*) :: Fin n -> Fin n -> Fin n #

negate :: Fin n -> Fin n #

abs :: Fin n -> Fin n #

signum :: Fin n -> Fin n #

fromInteger :: Integer -> Fin n #

Ord (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

compare :: Fin n -> Fin n -> Ordering #

(<) :: Fin n -> Fin n -> Bool #

(<=) :: Fin n -> Fin n -> Bool #

(>) :: Fin n -> Fin n -> Bool #

(>=) :: Fin n -> Fin n -> Bool #

max :: Fin n -> Fin n -> Fin n #

min :: Fin n -> Fin n -> Fin n #

PosC n => Read (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Show (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

showsPrec :: Int -> Fin n -> ShowS #

show :: Fin n -> String #

showList :: [Fin n] -> ShowS #

Generic (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Associated Types

type Rep (Fin n) :: Type -> Type #

Methods

from :: Fin n -> Rep (Fin n) x #

to :: Rep (Fin n) x -> Fin n #

Semigroup (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

(<>) :: Fin n -> Fin n -> Fin n #

sconcat :: NonEmpty (Fin n) -> Fin n #

stimes :: Integral b => b -> Fin n -> Fin n #

PosC n => Monoid (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

mempty :: Fin n #

mappend :: Fin n -> Fin n -> Fin n #

mconcat :: [Fin n] -> Fin n #

NFData (Fin n) Source # 
Instance details

Defined in Cybus.Fin

Methods

rnf :: Fin n -> () #

PosC n => Num1 (Fin n) Source # 
Instance details

Defined in Cybus.Fin

type Rep1 Fin Source # 
Instance details

Defined in Cybus.Fin

type Rep1 Fin = D1 ('MetaData "Fin" "Cybus.Fin" "cybus-0.3.0.0-2tgktn1zjvk47vpww9PCqf" 'False) (C1 ('MetaCons "Fin'" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos)))
type Rep (Fin n) Source # 
Instance details

Defined in Cybus.Fin

type Rep (Fin n) = D1 ('MetaData "Fin" "Cybus.Fin" "cybus-0.3.0.0-2tgktn1zjvk47vpww9PCqf" 'False) (C1 ('MetaCons "Fin'" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos)))

fnPos :: Fin n -> Pos Source #

accessor for the index position within a Fin

fnN :: Fin n -> Pos Source #

accessor for the maximum size within a Fin

pattern Fin :: forall (n :: Nat). Pos -> Pos -> Fin n Source #

readonly pattern synonym for fin

pattern FinU :: forall (n :: Nat). (HasCallStack, PosC n) => Pos -> Pos -> Fin n Source #

pattern synonym for validating the fin before construction with a PosC constraint for validating at the typelevel

class (PosC i, PosC n) => FinC i n where Source #

class for constraining "i" to positive numbers less than or equal to "n"

Methods

finC :: Fin n Source #

Instances

Instances details
(PosC n, i <=! n) => FinC i n Source # 
Instance details

Defined in Cybus.Fin

Methods

finC :: Fin n Source #

class FinWithMessageC msg i n Source #

class for constraining "i" to positive numbers less than or equal to "n" with a custom error message

Instances

Instances details
LTEQT msg i n => FinWithMessageC msg i n Source # 
Instance details

Defined in Cybus.Fin

read/show methods

showFin :: Fin n -> String Source #

pretty print Fin

readFinP :: forall n. PosC n => ReadP (Fin n) Source #

reader for showFin

readFin :: PosC n => ReadS (Fin n) Source #

reader for Fin

constructors

mkFinC :: forall n. PosC n => Pos -> Pos -> Either String (Fin n) Source #

create a Fin value level "i" and "n" values and validate against expected "n"

mkFin :: Pos -> Pos -> Either String (Fin n) Source #

create a Fin value level "i" and "n" values and validate that "i" is in range

fin :: PosC n => Int -> Either String (Fin n) Source #

convenience function for conversion from Int to Fin

finP :: forall n. PosC n => Pos -> Either String (Fin n) Source #

convenience function for conversion from Pos to Fin

fin indexes

_F1 :: FinC 1 n => Fin n Source #

type synonym for index 1

_F2 :: FinC 2 n => Fin n Source #

type synonym for index 2

_F3 :: FinC 3 n => Fin n Source #

type synonym for index 3

_F4 :: FinC 4 n => Fin n Source #

type synonym for index 4

_F5 :: FinC 5 n => Fin n Source #

type synonym for index 5

_F6 :: FinC 6 n => Fin n Source #

type synonym for index 6

_F7 :: FinC 7 n => Fin n Source #

type synonym for index 7

_F8 :: FinC 8 n => Fin n Source #

type synonym for index 8

_F9 :: FinC 9 n => Fin n Source #

type synonym for index 9

_F10 :: FinC 10 n => Fin n Source #

type synonym for index 10

_F11 :: FinC 11 n => Fin n Source #

type synonym for index 11

_F12 :: FinC 12 n => Fin n Source #

type synonym for index 12

_F13 :: FinC 13 n => Fin n Source #

type synonym for index 13

_F14 :: FinC 14 n => Fin n Source #

type synonym for index 14

_F15 :: FinC 15 n => Fin n Source #

type synonym for index 15

_F16 :: FinC 16 n => Fin n Source #

type synonym for index 16

_F17 :: FinC 17 n => Fin n Source #

type synonym for index 17

_F18 :: FinC 18 n => Fin n Source #

type synonym for index 18

_F19 :: FinC 19 n => Fin n Source #

type synonym for index 19

_F20 :: FinC 20 n => Fin n Source #

type synonym for index 20