data-diverse-4.7.1.0: Extensible records and polymorphic variants.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Diverse.Cases

Synopsis

Documentation

data Cases (fs :: [Type]) r (xs :: [Type]) Source #

Contains a Many of handlers/continuations for all the types in the xs typelist. This uses grab to get the unique handler for the type at the Head of xs.

Use cases to construct this with SameLength constraint to reduce programming confusion.

Instances

Instances details
UniqueMember (Head xs -> r) fs => Case (Cases fs r) xs Source #

UndecidableInstances because fs appears more often.

Instance details

Defined in Data.Diverse.Cases

Methods

case' :: Cases fs r xs -> Head xs -> CaseResult (Cases fs r) (Head xs) Source #

Reiterate (Cases fs r) xs Source # 
Instance details

Defined in Data.Diverse.Cases

Methods

reiterate :: Cases fs r xs -> Cases fs r (Tail xs) Source #

type CaseResult (Cases fs r :: [Type] -> TYPE LiftedRep) (x :: Type) Source # 
Instance details

Defined in Data.Diverse.Cases

type CaseResult (Cases fs r :: [Type] -> TYPE LiftedRep) (x :: Type) = r

cases :: forall r xs fs. (AllConstrained ((~) r) (CaseResults (Cases fs r) fs), SameLength fs (Nub xs)) => Many fs -> Cases fs r xs Source #

Create an instance of Case for either handling switching a Which.

let y = pick (5 :: Int) :: Which '[Int, Bool]
switch y (
    cases (show @Bool
        ./ show @Int
        ./ nul)) `shouldBe` "5"

Or for handling collect from a Many.

let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nul
    y = show @Int ./ show @Char ./ show @(Maybe Char) ./ show @Bool ./ nul
afoldr (:) [] (collect x (cases y)) `shouldBe`
    ["5", "False", "X", "Just 'O'", "6", "Just 'A'"]

This function imposes additional SameLength constraints than when using the Cases constructor directly. It is better practice to use cases to prevent programming confusion with dead code. However, the Cases constructor is still exported to allow creating a master-of-all-Case.

cases' :: forall r xs fs. AllConstrained ((~) r) (CaseResults (Cases fs r) fs) => Many fs -> Cases fs r xs Source #

A variation of cases without the SameLength constraint to allow creating a master-of-all-Case.

data CasesN (fs :: [Type]) r (n :: Nat) (xs :: [Type]) Source #

A variation of Cases which uses grabN to get the handler by index. There may be different handlers for the same type, but the handlers must be in the same order as the input xs typelist. Use casesN to construct this safely ensuring n starts at 0.

Instances

Instances details
ReiterateN (CasesN fs r) n xs Source # 
Instance details

Defined in Data.Diverse.Cases

Methods

reiterateN :: CasesN fs r n xs -> CasesN fs r (n + 1) (Tail xs) Source #

MemberAt n (Head xs -> r) fs => Case (CasesN fs r n) xs Source #

UndecidableInstances because fs appears more often.

Instance details

Defined in Data.Diverse.Cases

Methods

case' :: CasesN fs r n xs -> Head xs -> CaseResult (CasesN fs r n) (Head xs) Source #

type CaseResult (CasesN fs r n :: [Type] -> TYPE LiftedRep) (x :: Type) Source # 
Instance details

Defined in Data.Diverse.Cases

type CaseResult (CasesN fs r n :: [Type] -> TYPE LiftedRep) (x :: Type) = r

casesN :: forall r xs fs. (AllConstrained ((~) r) (CaseResults (CasesN fs r 0) fs), SameLength fs xs) => Many fs -> CasesN fs r 0 xs Source #

Safe Constructor for CasesN ensuring that the n Nat starts at 0. It is an instance of CaseN for either handling switchNing a Which in index order.

let y = pickN @0 Proxy (5 :: Int) :: Which '[Int, Bool, Bool, Int]
switchN y (
    casesN (show @Int
        ./ show @Bool
        ./ show @Bool
        ./ show @Int
        ./ nul)) `shouldBe` "5"

Or for handling collectN from a Many.

let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nul
    y = show @Int ./ show @Bool ./ show @Char ./ show @(Maybe Char) ./ show @Int ./ show @(Maybe Char) ./ nul
afoldr (:) [] (collectN x (casesN y)) `shouldBe`
    ["5", "False", "X", "Just 'O'", "6", "Just 'A'"]

casesN' :: forall r xs fs. AllConstrained ((~) r) (CaseResults (CasesN fs r 0) fs) => Many fs -> CasesN fs r 0 xs Source #

A variation of casesN without the SameLength constraint to allow creating a master-of-all-Case.