Get-0.2018.1.10: get stuff out of stuff

Safe HaskellNone
LanguageHaskell2010

Control.Get

Documentation

data And x y Source #

Constructors

And x y 

Instances

(TryGet as a self aOK, TryGetAndR as b self aOK andOK) => TryGet as (And a b) self andOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * (And a b) -> Proxy * as -> Sing Bool andOK Source #

tryGetVal :: self -> And a b -> Proxy * as -> If * andOK as () Source #

tryGet :: self -> And a b -> Proxy * as -> (If * andOK as (), Sing Bool andOK) Source #

(TryGet a from self aOK, TryGetAndL a b from self aOK andOK) => TryGet (And a b) from self andOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * from -> Proxy * (And a b) -> Sing Bool andOK Source #

tryGetVal :: self -> from -> Proxy * (And a b) -> If * andOK (And a b) () Source #

tryGet :: self -> from -> Proxy * (And a b) -> (If * andOK (And a b) (), Sing Bool andOK) Source #

data Or x y Source #

Constructors

OrLeft x 
OrRight y 

Instances

(TryGet as a self aOK, TryGetOrR as b self aOK orOK) => TryGet as (Or a b) self orOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * (Or a b) -> Proxy * as -> Sing Bool orOK Source #

tryGetVal :: self -> Or a b -> Proxy * as -> If * orOK as () Source #

tryGet :: self -> Or a b -> Proxy * as -> (If * orOK as (), Sing Bool orOK) Source #

(TryGet a from self aOK, TryGetOrL a b from self aOK orOK) => TryGet (Or a b) from self orOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * from -> Proxy * (Or a b) -> Sing Bool orOK Source #

tryGetVal :: self -> from -> Proxy * (Or a b) -> If * orOK (Or a b) () Source #

tryGet :: self -> from -> Proxy * (Or a b) -> (If * orOK (Or a b) (), Sing Bool orOK) Source #

data Bottom Source #

Instances

TryGet as Bottom self True Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * Bottom -> Proxy * as -> Sing Bool True Source #

tryGetVal :: self -> Bottom -> Proxy * as -> If * True as () Source #

tryGet :: self -> Bottom -> Proxy * as -> (If * True as (), Sing Bool True) Source #

data Top Source #

Constructors

Top 

Instances

(~) Bool ok False => TryGet as Top self ok Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * Top -> Proxy * as -> Sing Bool ok Source #

tryGetVal :: self -> Top -> Proxy * as -> If * ok as () Source #

tryGet :: self -> Top -> Proxy * as -> (If * ok as (), Sing Bool ok) Source #

TryGet Top from self True Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * from -> Proxy * Top -> Sing Bool True Source #

tryGetVal :: self -> from -> Proxy * Top -> If * True Top () Source #

tryGet :: self -> from -> Proxy * Top -> (If * True Top (), Sing Bool True) Source #

fromVal :: a -> Proxy a Source #

class TryGet as from self ok | as from self -> ok where Source #

Minimal complete definition

tryGetSing, tryGetVal

Methods

tryGetSing :: Proxy self -> Proxy from -> Proxy as -> Sing ok Source #

tryGetVal :: self -> from -> Proxy as -> If ok as () Source #

tryGet :: self -> from -> Proxy as -> (If ok as (), Sing ok) Source #

Instances

(~) Bool ok True => TryGet a a self ok Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * a -> Proxy * a -> Sing Bool ok Source #

tryGetVal :: self -> a -> Proxy * a -> If * ok a () Source #

tryGet :: self -> a -> Proxy * a -> (If * ok a (), Sing Bool ok) Source #

TryGet as Bottom self True Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * Bottom -> Proxy * as -> Sing Bool True Source #

tryGetVal :: self -> Bottom -> Proxy * as -> If * True as () Source #

tryGet :: self -> Bottom -> Proxy * as -> (If * True as (), Sing Bool True) Source #

(~) Bool ok False => TryGet as Top self ok Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * Top -> Proxy * as -> Sing Bool ok Source #

tryGetVal :: self -> Top -> Proxy * as -> If * ok as () Source #

tryGet :: self -> Top -> Proxy * as -> (If * ok as (), Sing Bool ok) Source #

TryGet Top from self True Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * from -> Proxy * Top -> Sing Bool True Source #

tryGetVal :: self -> from -> Proxy * Top -> If * True Top () Source #

tryGet :: self -> from -> Proxy * Top -> (If * True Top (), Sing Bool True) Source #

TryGet as from from ok => TryGet as (Protected from) self ok Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * (Protected from) -> Proxy * as -> Sing Bool ok Source #

tryGetVal :: self -> Protected from -> Proxy * as -> If * ok as () Source #

tryGet :: self -> Protected from -> Proxy * as -> (If * ok as (), Sing Bool ok) Source #

(TryGet as a self aOK, TryGetOrR as b self aOK orOK) => TryGet as (Or a b) self orOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * (Or a b) -> Proxy * as -> Sing Bool orOK Source #

tryGetVal :: self -> Or a b -> Proxy * as -> If * orOK as () Source #

tryGet :: self -> Or a b -> Proxy * as -> (If * orOK as (), Sing Bool orOK) Source #

(TryGet as a self aOK, TryGetAndR as b self aOK andOK) => TryGet as (And a b) self andOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * (And a b) -> Proxy * as -> Sing Bool andOK Source #

tryGetVal :: self -> And a b -> Proxy * as -> If * andOK as () Source #

tryGet :: self -> And a b -> Proxy * as -> (If * andOK as (), Sing Bool andOK) Source #

(TryGet a from self aOK, TryGetOrL a b from self aOK orOK) => TryGet (Or a b) from self orOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * from -> Proxy * (Or a b) -> Sing Bool orOK Source #

tryGetVal :: self -> from -> Proxy * (Or a b) -> If * orOK (Or a b) () Source #

tryGet :: self -> from -> Proxy * (Or a b) -> (If * orOK (Or a b) (), Sing Bool orOK) Source #

(TryGet a from self aOK, TryGetAndL a b from self aOK andOK) => TryGet (And a b) from self andOK Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * from -> Proxy * (And a b) -> Sing Bool andOK Source #

tryGetVal :: self -> from -> Proxy * (And a b) -> If * andOK (And a b) () Source #

tryGet :: self -> from -> Proxy * (And a b) -> (If * andOK (And a b) (), Sing Bool andOK) Source #

class TryGet as from from True => Get as from where Source #

Methods

get :: from -> as Source #

Instances

TryGet as from from True => Get as from Source # 

Methods

get :: from -> as Source #

andLeftP :: Proxy (And l r) -> Proxy l Source #

class TryGetAndL a b from self (aOK :: Bool) (andOK :: Bool) | b from self aOK -> andOK where Source #

Minimal complete definition

tryGetAndLVal, tryGetAndLSing

Methods

tryGetAndLVal :: self -> from -> (If aOK a (), Sing aOK) -> Proxy (And a b) -> If andOK (And a b) () Source #

tryGetAndLSing :: Proxy self -> Proxy from -> Sing aOK -> Proxy (And a b) -> Sing andOK Source #

Instances

TryGet b from self andOK => TryGetAndL a b from self True andOK Source # 

Methods

tryGetAndLVal :: self -> from -> (If * True a (), Sing Bool True) -> Proxy * (And a b) -> If * andOK (And a b) () Source #

tryGetAndLSing :: Proxy * self -> Proxy * from -> Sing Bool True -> Proxy * (And a b) -> Sing Bool andOK Source #

TryGetAndL a b from self False False Source # 

Methods

tryGetAndLVal :: self -> from -> (If * False a (), Sing Bool False) -> Proxy * (And a b) -> If * False (And a b) () Source #

tryGetAndLSing :: Proxy * self -> Proxy * from -> Sing Bool False -> Proxy * (And a b) -> Sing Bool False Source #

class TryGetAndR as b self (aOK :: Bool) (andOK :: Bool) | as b self aOK -> andOK where Source #

Minimal complete definition

tryGetAndRVal, tryGetAndRSing

Methods

tryGetAndRVal :: self -> (If aOK as (), Sing aOK) -> b -> Proxy as -> If andOK as () Source #

tryGetAndRSing :: Proxy self -> Sing aOK -> Proxy b -> Proxy as -> Sing andOK Source #

Instances

TryGet as b self andOK => TryGetAndR as b self False andOK Source # 

Methods

tryGetAndRVal :: self -> (If * False as (), Sing Bool False) -> b -> Proxy * as -> If * andOK as () Source #

tryGetAndRSing :: Proxy * self -> Sing Bool False -> Proxy * b -> Proxy * as -> Sing Bool andOK Source #

TryGetAndR as b self True True Source # 

Methods

tryGetAndRVal :: self -> (If * True as (), Sing Bool True) -> b -> Proxy * as -> If * True as () Source #

tryGetAndRSing :: Proxy * self -> Sing Bool True -> Proxy * b -> Proxy * as -> Sing Bool True Source #

orLeftP :: Proxy (Or l r) -> Proxy l Source #

orRightP :: Proxy (Or l r) -> Proxy r Source #

class TryGetOrL a b from self (aOK :: Bool) (orOK :: Bool) | b from self aOK -> orOK where Source #

Minimal complete definition

tryGetOrLVal, tryGetOrLSing

Methods

tryGetOrLVal :: self -> from -> (If aOK a (), Sing aOK) -> Proxy (Or a b) -> If orOK (Or a b) () Source #

tryGetOrLSing :: Proxy self -> Proxy from -> Sing aOK -> Proxy (Or a b) -> Sing orOK Source #

Instances

TryGet b from self orOK => TryGetOrL a b from self False orOK Source # 

Methods

tryGetOrLVal :: self -> from -> (If * False a (), Sing Bool False) -> Proxy * (Or a b) -> If * orOK (Or a b) () Source #

tryGetOrLSing :: Proxy * self -> Proxy * from -> Sing Bool False -> Proxy * (Or a b) -> Sing Bool orOK Source #

TryGetOrL a b from self True True Source # 

Methods

tryGetOrLVal :: self -> from -> (If * True a (), Sing Bool True) -> Proxy * (Or a b) -> If * True (Or a b) () Source #

tryGetOrLSing :: Proxy * self -> Proxy * from -> Sing Bool True -> Proxy * (Or a b) -> Sing Bool True Source #

class TryGetOrR as b self (aOK :: Bool) orOK | as b self aOK -> orOK where Source #

Minimal complete definition

tryGetOrRVal, tryGetOrRSing, tryGetOrRUnify

Methods

tryGetOrRVal :: self -> b -> Sing aOK -> Proxy as -> If orOK as () Source #

tryGetOrRSing :: Proxy self -> Proxy b -> Sing aOK -> Proxy as -> Sing orOK Source #

tryGetOrRUnify :: Proxy self -> Proxy b -> Sing aOK -> Proxy as -> Dict (orOK ~ True) -> Dict (aOK ~ True) Source #

Instances

TryGet as b self orOK => TryGetOrR as b self True orOK Source # 

Methods

tryGetOrRVal :: self -> b -> Sing Bool True -> Proxy * as -> If * orOK as () Source #

tryGetOrRSing :: Proxy * self -> Proxy * b -> Sing Bool True -> Proxy * as -> Sing Bool orOK Source #

tryGetOrRUnify :: Proxy * self -> Proxy * b -> Sing Bool True -> Proxy * as -> Dict ((Bool ~ orOK) True) -> Dict ((Bool ~ True) True) Source #

TryGetOrR as b self False False Source # 

Methods

tryGetOrRVal :: self -> b -> Sing Bool False -> Proxy * as -> If * False as () Source #

tryGetOrRSing :: Proxy * self -> Proxy * b -> Sing Bool False -> Proxy * as -> Sing Bool False Source #

tryGetOrRUnify :: Proxy * self -> Proxy * b -> Sing Bool False -> Proxy * as -> Dict ((Bool ~ False) True) -> Dict ((Bool ~ False) True) Source #

newtype Protected x Source #

Constructors

Protected 

Fields

Instances

TryGet as from from ok => TryGet as (Protected from) self ok Source # 

Methods

tryGetSing :: Proxy * self -> Proxy * (Protected from) -> Proxy * as -> Sing Bool ok Source #

tryGetVal :: self -> Protected from -> Proxy * as -> If * ok as () Source #

tryGet :: self -> Protected from -> Proxy * as -> (If * ok as (), Sing Bool ok) Source #