wakame-0.1.0.0: Functions to manipulate records

Safe HaskellNone
LanguageHaskell2010

Wakame.Generics

Contents

Synopsis

Documentation

>>> import Wakame
>>> data Point = Point { x :: Double, y :: Double } deriving (Show, Generic)

Internal

class IsRow' f where Source #

Associated Types

type Of' f :: [FIELD] Source #

Methods

fromRow' :: Row (Of' f) -> f a Source #

toRow' :: f a -> Row (Of' f) Source #

Instances
IsRow' (U1 :: k -> Type) Source # 
Instance details

Defined in Wakame.Generics

Associated Types

type Of' U1 :: [FIELD] Source #

Methods

fromRow' :: Row (Of' U1) -> U1 a Source #

toRow' :: U1 a -> Row (Of' U1) Source #

IsRow' (S1 (MetaSel (Nothing :: Maybe Symbol) su ss ds) (Rec0 (V ((,) key a))) :: k -> Type) Source # 
Instance details

Defined in Wakame.Generics

Associated Types

type Of' (S1 (MetaSel Nothing su ss ds) (Rec0 (V (key, a)))) :: [FIELD] Source #

Methods

fromRow' :: Row (Of' (S1 (MetaSel Nothing su ss ds) (Rec0 (V (key, a))))) -> S1 (MetaSel Nothing su ss ds) (Rec0 (V (key, a))) a0 Source #

toRow' :: S1 (MetaSel Nothing su ss ds) (Rec0 (V (key, a))) a0 -> Row (Of' (S1 (MetaSel Nothing su ss ds) (Rec0 (V (key, a))))) Source #

IsRow' (S1 (MetaSel (Just key) su ss ds) (Rec0 a) :: k -> Type) Source # 
Instance details

Defined in Wakame.Generics

Associated Types

type Of' (S1 (MetaSel (Just key) su ss ds) (Rec0 a)) :: [FIELD] Source #

Methods

fromRow' :: Row (Of' (S1 (MetaSel (Just key) su ss ds) (Rec0 a))) -> S1 (MetaSel (Just key) su ss ds) (Rec0 a) a0 Source #

toRow' :: S1 (MetaSel (Just key) su ss ds) (Rec0 a) a0 -> Row (Of' (S1 (MetaSel (Just key) su ss ds) (Rec0 a))) Source #

(IsRow' a, IsRow' b, l ~ Of' a, r ~ Of' b, Union l r (l ++ r)) => IsRow' (a :*: b :: k -> Type) Source # 
Instance details

Defined in Wakame.Generics

Associated Types

type Of' (a :*: b) :: [FIELD] Source #

Methods

fromRow' :: Row (Of' (a :*: b)) -> (a :*: b) a0 Source #

toRow' :: (a :*: b) a0 -> Row (Of' (a :*: b)) Source #

IsRow' f => IsRow' (C1 i f :: k -> Type) Source # 
Instance details

Defined in Wakame.Generics

Associated Types

type Of' (C1 i f) :: [FIELD] Source #

Methods

fromRow' :: Row (Of' (C1 i f)) -> C1 i f a Source #

toRow' :: C1 i f a -> Row (Of' (C1 i f)) Source #

IsRow' f => IsRow' (D1 i f :: k -> Type) Source # 
Instance details

Defined in Wakame.Generics

Associated Types

type Of' (D1 i f) :: [FIELD] Source #

Methods

fromRow' :: Row (Of' (D1 i f)) -> D1 i f a Source #

toRow' :: D1 i f a -> Row (Of' (D1 i f)) Source #

Orphan instances

(Generic a, IsRow' (Rep a)) => IsRow a Source #

Instance of IsRow over generic rep >>> :kind! Of Point Of Point :: [(Symbol, *)] = '[ '("x", Double), '("y", Double)]

>>> toRow' $ from $ Point 1.2 8.3
(x: 1.2) :* (y: 8.3) :* Nil
>>> to @Point $ fromRow' $ keyed @"x" 1.2 :* keyed @"y" 8.3 :* Nil
Point {x = 1.2, y = 8.3}
Instance details

Associated Types

type Of a :: [FIELD] Source #

Methods

fromRow :: Row (Of a) -> a Source #

toRow :: a -> Row (Of a) Source #