superrecord-0.1.0.0: Supercharged anonymous records

Safe HaskellNone
LanguageHaskell2010

SuperRecord

Contents

Synopsis

Basics

data label := value infix 6 Source #

Field named l labels value of type t adapted from the awesome labels package. Example: (#name := "Chris") :: ("name" := String)

Constructors

KnownSymbol label => (FldProxy label) := !value infix 6 

Instances

(RecEq rts (RemoveAccessTo l lts), Has l rts idx s v, Eq v) => RecEq rts ((:) * ((:=) l t) lts) Source # 

Methods

recEq :: Rec rts -> Rec rts -> Proxy [*] ((* ': (l := t)) lts) -> Bool Source #

(KnownSymbol l, RecApply rts (RemoveAccessTo l lts) c, Has l rts idx s v, c v) => RecApply rts ((:) * ((:=) l t) lts) c Source # 

Methods

recApply :: (forall a. Dict (c a) -> String -> a -> r) -> Rec rts -> Proxy [*] ((* ': (l := t)) lts) -> [r] Source #

Eq value => Eq ((:=) label value) Source # 

Methods

(==) :: (label := value) -> (label := value) -> Bool #

(/=) :: (label := value) -> (label := value) -> Bool #

Ord value => Ord ((:=) label value) Source # 

Methods

compare :: (label := value) -> (label := value) -> Ordering #

(<) :: (label := value) -> (label := value) -> Bool #

(<=) :: (label := value) -> (label := value) -> Bool #

(>) :: (label := value) -> (label := value) -> Bool #

(>=) :: (label := value) -> (label := value) -> Bool #

max :: (label := value) -> (label := value) -> label := value #

min :: (label := value) -> (label := value) -> label := value #

Show t => Show ((:=) l t) Source # 

Methods

showsPrec :: Int -> (l := t) -> ShowS #

show :: (l := t) -> String #

showList :: [l := t] -> ShowS #

(KnownSymbol l, FromJSON t, RecJsonParse lts, (~) Nat (RecSize lts) s, KnownNat s) => RecJsonParse ((:) * ((:=) l t) lts) Source # 

Methods

recJsonParse :: Int -> Object -> Parser (Rec ((* ': (l := t)) lts)) Source #

(KnownSymbol l, RecKeys lts) => RecKeys ((:) * ((:=) l t) lts) Source # 

Associated Types

type RecKeysT ((:) * ((:=) l t) lts :: [*]) :: [Symbol] Source #

Methods

recKeys :: t ((* ': (l := t)) lts) -> [String] Source #

(Has l rts idx s v, NFData v, RecNfData (RemoveAccessTo l lts) rts) => RecNfData ((:) * ((:=) l t) lts) rts Source # 

Methods

recNfData :: Proxy [*] ((* ': (l := t)) lts) -> Rec rts -> () Source #

type RecKeysT ((:) * ((:=) l t) lts) Source # 
type RecKeysT ((:) * ((:=) l t) lts) = (:) Symbol l (RecKeysT lts)

data Rec lts Source #

The core record type.

Instances

RecEq lts lts => Eq (Rec lts) Source # 

Methods

(==) :: Rec lts -> Rec lts -> Bool #

(/=) :: Rec lts -> Rec lts -> Bool #

RecApply lts lts Show => Show (Rec lts) Source # 

Methods

showsPrec :: Int -> Rec lts -> ShowS #

show :: Rec lts -> String #

showList :: [Rec lts] -> ShowS #

RecApply lts lts ToJSON => ToJSON (Rec lts) Source # 

Methods

toJSON :: Rec lts -> Value #

toEncoding :: Rec lts -> Encoding #

toJSONList :: [Rec lts] -> Value #

toEncodingList :: [Rec lts] -> Encoding #

((~) Nat (RecSize lts) s, KnownNat s, RecJsonParse lts) => FromJSON (Rec lts) Source # 

Methods

parseJSON :: Value -> Parser (Rec lts) #

parseJSONList :: Value -> Parser [Rec lts] #

RecNfData lts lts => NFData (Rec lts) Source # 

Methods

rnf :: Rec lts -> () #

(SetPath more v, Has l lts idx s v, (~) * (RecDeepTy * ((:) Symbol l more) (Rec lts)) (RecDeepTy * more v)) => SetPath ((:) Symbol l more) (Rec lts) Source # 

Methods

setPath :: SPath ((Symbol ': l) more) -> RecDeepTy * ((Symbol ': l) more) (Rec lts) -> Rec lts -> Rec lts Source #

rnil :: Rec '[] Source #

An empty record

rcons :: forall l t lts s. (RecSize lts ~ s, KnownNat s) => (l := t) -> Rec lts -> Rec ((l := t) ': lts) Source #

Prepend a record entry to a record Rec

(&) :: forall l t lts s. (RecSize lts ~ s, KnownNat s) => (l := t) -> Rec lts -> Rec ((l := t) ': lts) infixr 5 Source #

Alias for rcons

type Has l lts idx s v = (RecTyIdxH 0 l lts ~ idx, RecIdxTyH idx 0 lts ~ v, KnownNat idx, RecSize lts ~ s, KnownNat s) Source #

State that a record contains a label. Leave idx an s free variables, used internally

get :: forall l v lts idx s. Has l lts idx s v => FldProxy l -> Rec lts -> v Source #

Get an existing record field

(&.) :: forall l v lts idx s. Has l lts idx s v => Rec lts -> FldProxy l -> v infixl 3 Source #

Alias for get

set :: forall l v lts idx s. Has l lts idx s v => FldProxy l -> v -> Rec lts -> Rec lts Source #

Update an existing record field

class SetPath k x where Source #

Minimal complete definition

setPath

Methods

setPath :: SPath k -> RecDeepTy k x -> x -> x Source #

Perform a deep update, setting the key along the path to the desired value

Instances

SetPath ([] Symbol) v Source # 

Methods

setPath :: SPath [Symbol] -> RecDeepTy * [Symbol] v -> v -> v Source #

(SetPath more v, Has l lts idx s v, (~) * (RecDeepTy * ((:) Symbol l more) (Rec lts)) (RecDeepTy * more v)) => SetPath ((:) Symbol l more) (Rec lts) Source # 

Methods

setPath :: SPath ((Symbol ': l) more) -> RecDeepTy * ((Symbol ': l) more) (Rec lts) -> Rec lts -> Rec lts Source #

data SPath t where Source #

Path to the key that should be updated

Constructors

SCons :: FldProxy l -> SPath ls -> SPath (l ': ls) 
SNil :: SPath '[] 

(&:) :: FldProxy l -> SPath ls -> SPath (l ': ls) infixr 8 Source #

Alias for SCons

snil :: SPath '[] Source #

Alias for SNil

Reflection

reflectRec :: forall c r lts. RecApply lts lts c => Proxy c -> (forall a. c a => String -> a -> r) -> Rec lts -> [r] Source #

Apply a function to each key element pair for a record

class RecApply rts lts c where Source #

Machinery needed to implement reflectRec

Minimal complete definition

recApply

Methods

recApply :: (forall a. Dict (c a) -> String -> a -> r) -> Rec rts -> Proxy lts -> [r] Source #

Instances

RecApply rts ([] *) c Source # 

Methods

recApply :: (forall a. Dict (c a) -> String -> a -> r) -> Rec rts -> Proxy [*] [*] -> [r] Source #

(KnownSymbol l, RecApply rts (RemoveAccessTo l lts) c, Has l rts idx s v, c v) => RecApply rts ((:) * ((:=) l t) lts) c Source # 

Methods

recApply :: (forall a. Dict (c a) -> String -> a -> r) -> Rec rts -> Proxy [*] ((* ': (l := t)) lts) -> [r] Source #

Machinery

type family RecTyIdxH (i :: Nat) (l :: Symbol) (lts :: [*]) :: Nat where ... Source #

Equations

RecTyIdxH idx l ((l := t) ': lts) = idx 
RecTyIdxH idx m ((l := t) ': lts) = RecTyIdxH (1 + idx) m lts 
RecTyIdxH idx m '[] = TypeError (Text "Could not find label " :<>: Text m) 

type family RecIdxTyH (i :: Nat) (r :: Nat) (lts :: [*]) :: * where ... Source #

Equations

RecIdxTyH idx idx ((l := t) ': lts) = t 
RecIdxTyH idx other ((l := t) ': lts) = RecIdxTyH idx (other + 1) lts 
RecIdxTyH idx other '[] = TypeError (Text "Could not find index " :<>: ShowType idx) 

showRec :: forall lts. RecApply lts lts Show => Rec lts -> [(String, String)] Source #

Convert all elements of a record to a String

class RecKeys lts where Source #

Get keys of a record on value and type level

Minimal complete definition

recKeys

Associated Types

type RecKeysT lts :: [Symbol] Source #

Methods

recKeys :: t lts -> [String] Source #

Instances

RecKeys ([] *) Source # 

Associated Types

type RecKeysT ([] * :: [*]) :: [Symbol] Source #

Methods

recKeys :: t [*] -> [String] Source #

(KnownSymbol l, RecKeys lts) => RecKeys ((:) * ((:=) l t) lts) Source # 

Associated Types

type RecKeysT ((:) * ((:=) l t) lts :: [*]) :: [Symbol] Source #

Methods

recKeys :: t ((* ': (l := t)) lts) -> [String] Source #

class RecEq rts lts where Source #

Machinery to implement equality

Minimal complete definition

recEq

Methods

recEq :: Rec rts -> Rec rts -> Proxy lts -> Bool Source #

Instances

RecEq rts ([] *) Source # 

Methods

recEq :: Rec rts -> Rec rts -> Proxy [*] [*] -> Bool Source #

(RecEq rts (RemoveAccessTo l lts), Has l rts idx s v, Eq v) => RecEq rts ((:) * ((:=) l t) lts) Source # 

Methods

recEq :: Rec rts -> Rec rts -> Proxy [*] ((* ': (l := t)) lts) -> Bool Source #

recToValue :: forall lts. RecApply lts lts ToJSON => Rec lts -> Value Source #

recToEncoding :: forall lts. RecApply lts lts ToJSON => Rec lts -> Encoding Source #

recJsonParser :: forall lts s. (RecSize lts ~ s, KnownNat s, RecJsonParse lts) => Value -> Parser (Rec lts) Source #

class RecJsonParse lts where Source #

Machinery to implement parseJSON

Minimal complete definition

recJsonParse

Methods

recJsonParse :: Int -> Object -> Parser (Rec lts) Source #

Instances

RecJsonParse ([] *) Source # 

Methods

recJsonParse :: Int -> Object -> Parser (Rec [*]) Source #

(KnownSymbol l, FromJSON t, RecJsonParse lts, (~) Nat (RecSize lts) s, KnownNat s) => RecJsonParse ((:) * ((:=) l t) lts) Source # 

Methods

recJsonParse :: Int -> Object -> Parser (Rec ((* ': (l := t)) lts)) Source #

class RecNfData lts rts where Source #

Machinery for NFData

Minimal complete definition

recNfData

Methods

recNfData :: Proxy lts -> Rec rts -> () Source #

Instances

RecNfData ([] *) rts Source # 

Methods

recNfData :: Proxy [*] [*] -> Rec rts -> () Source #

(Has l rts idx s v, NFData v, RecNfData (RemoveAccessTo l lts) rts) => RecNfData ((:) * ((:=) l t) lts) rts Source # 

Methods

recNfData :: Proxy [*] ((* ': (l := t)) lts) -> Rec rts -> () Source #

type family RecSize (lts :: [*]) :: Nat where ... Source #

Equations

RecSize '[] = 0 
RecSize ((l := t) ': lts) = 1 + RecSize lts 

type family RemoveAccessTo (l :: Symbol) (lts :: [*]) :: [*] where ... Source #

Equations

RemoveAccessTo l ((l := t) ': lts) = RemoveAccessTo l lts 
RemoveAccessTo q ((l := t) ': lts) = (l := t) ': RemoveAccessTo l lts 
RemoveAccessTo q '[] = '[] 

data FldProxy t Source #

A proxy witness for a label. Very similar to Proxy, but needed to implement a non-orphan IsLabel instance

Constructors

FldProxy 

Instances

type family RecDeepTy (ls :: [Symbol]) (lts :: k) :: * where ... Source #

Equations

RecDeepTy (l ': more) (Rec q) = RecDeepTy (l ': more) q 
RecDeepTy (l ': more) ((l := Rec t) ': lts) = RecDeepTy more t 
RecDeepTy (l ': more) ((l := t) ': lts) = t 
RecDeepTy (l ': more) ((q := t) ': lts) = RecDeepTy (l ': more) lts 
RecDeepTy '[] v = v