Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- class App repr where
- (<.>) :: repr a b -> repr b c -> repr a c
- class Alt repr where
- data a :!: b = a :!: b
- class Pro repr where
- dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k
- class AltApp repr where
- class Permutable repr where
- type Permutation (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr
- runPermutation :: Permutation repr k a -> repr (a -> k) k
- toPermutation :: repr (a -> k) k -> Permutation repr k a
- toPermDefault :: a -> repr (a -> k) k -> Permutation repr k a
- (<?>) :: App repr => Permutable repr => Permutation repr b a -> repr b c -> repr (a -> b) c
- class Sequenceable repr where
- type Sequence (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr
- runSequence :: Sequence repr k a -> repr (a -> k) k
- toSequence :: repr (a -> k) k -> Sequence repr k a
- type Name = String
- type Segment = String
- class CLI_Command repr where
- class CLI_Var repr where
- type VarConstraint repr a :: Constraint
- var' :: VarConstraint repr a => Name -> repr (a -> k) k
- just :: a -> repr (a -> k) k
- nothing :: repr k k
- var :: forall a k repr. CLI_Var repr => VarConstraint repr a => Name -> repr (a -> k) k
- class CLI_Env repr where
- type EnvConstraint repr a :: Constraint
- env' :: EnvConstraint repr a => Name -> repr (a -> k) k
- env :: forall a k repr. CLI_Env repr => EnvConstraint repr a => Name -> repr (a -> k) k
- data Tag
- class (App repr, Permutable repr, CLI_Var repr) => CLI_Tag repr where
- type TagConstraint repr a :: Constraint
- tag :: Tag -> repr f k -> repr f k
- endOpts :: repr k k
- flag :: TagConstraint repr Bool => Tag -> Permutation repr k Bool
- optionalTag :: TagConstraint repr a => AltApp repr => Alt repr => Pro repr => Tag -> repr (a -> k) k -> Permutation repr k (Maybe a)
- defaultTag :: TagConstraint repr a => Tag -> a -> repr (a -> k) k -> Permutation repr k a
- requiredTag :: TagConstraint repr a => Tag -> repr (a -> k) k -> Permutation repr k a
- many0Tag :: TagConstraint repr a => AltApp repr => Tag -> repr (a -> k) k -> Permutation repr k [a]
- many1Tag :: TagConstraint repr a => AltApp repr => Tag -> repr (a -> k) k -> Permutation repr k [a]
- class CLI_Response repr where
- type ResponseConstraint repr a :: Constraint
- type ResponseArgs repr a :: *
- type Response repr :: *
- response' :: ResponseConstraint repr a => repr (ResponseArgs repr a) (Response repr)
- response :: forall a repr. CLI_Response repr => ResponseConstraint repr a => repr (ResponseArgs repr a) (Response repr)
- class CLI_Help repr where
- type HelpConstraint repr d :: Constraint
- help :: HelpConstraint repr d => d -> repr f k -> repr f k
- program :: Name -> repr f k -> repr f k
- rule :: Name -> repr f k -> repr f k
- class Trans repr where
Class App
Nothing
(<.>) :: repr a b -> repr b c -> repr a c infixr 4 Source #
(<.>) :: Trans repr => App (UnTrans repr) => repr a b -> repr b c -> repr a c infixr 4 Source #
Class Alt
Nothing
(<!>) :: repr a k -> repr b k -> repr (a :!: b) k infixr 3 Source #
alt :: repr a k -> repr a k -> repr a k infixr 3 Source #
opt :: repr (a -> k) k -> repr (Maybe a -> k) k Source #
(<!>) :: Trans repr => Alt (UnTrans repr) => repr a k -> repr b k -> repr (a :!: b) k infixr 3 Source #
alt :: Trans repr => Alt (UnTrans repr) => repr a k -> repr a k -> repr a k infixr 3 Source #
opt :: Trans repr => Alt (UnTrans repr) => repr (a -> k) k -> repr (Maybe a -> k) k Source #
Type (:!:
)
Class Pro
Nothing
dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #
dimap :: Trans repr => Pro (UnTrans repr) => (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #
Class AltApp
class AltApp repr where Source #
Nothing
many0 :: repr (a -> k) k -> repr ([a] -> k) k Source #
many1 :: repr (a -> k) k -> repr ([a] -> k) k Source #
many0 :: Trans repr => AltApp (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #
many1 :: Trans repr => AltApp (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #
Class Permutable
class Permutable repr where Source #
type Permutation (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr Source #
runPermutation :: Permutation repr k a -> repr (a -> k) k Source #
toPermutation :: repr (a -> k) k -> Permutation repr k a Source #
toPermDefault :: a -> repr (a -> k) k -> Permutation repr k a Source #
Instances
(<?>) :: App repr => Permutable repr => Permutation repr b a -> repr b c -> repr (a -> b) c infixr 4 Source #
Convenient wrapper to omit a runPermutation
.
opts<?>
next =runPermutation
opts<.>
next
Class Sequenceable
class Sequenceable repr where Source #
runSequence :: Sequence repr k a -> repr (a -> k) k Source #
toSequence :: repr (a -> k) k -> Sequence repr k a Source #
Instances
Ord e => Sequenceable (Router (Parser e d)) Source # | |
SchemaDoc d => Sequenceable (Schema d) Source # | |
(LayoutDoc d, Justifiable d) => Sequenceable (Layout d) Source # | |
Ord e => Sequenceable (Parser e d) Source # | |
Type Name
Type Segment
Class CLI_Command
class CLI_Command repr where Source #
Class CLI_Var
class CLI_Var repr where Source #
Nothing
type VarConstraint repr a :: Constraint Source #
var' :: VarConstraint repr a => Name -> repr (a -> k) k Source #
just :: a -> repr (a -> k) k Source #
var' :: Trans repr => CLI_Var (UnTrans repr) => VarConstraint (UnTrans repr) a => Name -> repr (a -> k) k Source #
just :: Trans repr => CLI_Var (UnTrans repr) => a -> repr (a -> k) k Source #
nothing :: Trans repr => CLI_Var (UnTrans repr) => repr k k Source #
var :: forall a k repr. CLI_Var repr => VarConstraint repr a => Name -> repr (a -> k) k Source #
Like var'
but with the type variable (a)
first instead or (repr)
so it can be passed using TypeApplications
without adding a |@_| for (repr)
.
Class CLI_Env
class CLI_Env repr where Source #
Nothing
type EnvConstraint repr a :: Constraint Source #
env' :: EnvConstraint repr a => Name -> repr (a -> k) k Source #
env' :: Trans repr => CLI_Env (UnTrans repr) => EnvConstraint (UnTrans repr) a => Name -> repr (a -> k) k Source #
Instances
Ord e => CLI_Env (Router (Parser e d)) Source # | |
Defined in Symantic.CLI.Parser type EnvConstraint (Router (Parser e d)) a :: Constraint Source # | |
SchemaDoc d => CLI_Env (Schema d) Source # | |
Defined in Symantic.CLI.Schema type EnvConstraint (Schema d) a :: Constraint Source # | |
LayoutDoc d => CLI_Env (Layout d) Source # | |
Defined in Symantic.CLI.Layout type EnvConstraint (Layout d) a :: Constraint Source # | |
SchemaDoc d => CLI_Env (Help d) Source # | |
Defined in Symantic.CLI.Help type EnvConstraint (Help d) a :: Constraint Source # | |
Ord e => CLI_Env (Parser e d) Source # | |
Defined in Symantic.CLI.Parser type EnvConstraint (Parser e d) a :: Constraint Source # |
env :: forall a k repr. CLI_Env repr => EnvConstraint repr a => Name -> repr (a -> k) k Source #
Like env'
but with the type enviable (a)
first instead or (repr)
so it can be passed using TypeApplications
without adding a |@_| for (repr)
.
Type Tag
Class CLI_Tag
class (App repr, Permutable repr, CLI_Var repr) => CLI_Tag repr where Source #
Nothing
type TagConstraint repr a :: Constraint Source #
tag :: Tag -> repr f k -> repr f k Source #
flag :: TagConstraint repr Bool => Tag -> Permutation repr k Bool Source #
optionalTag :: TagConstraint repr a => AltApp repr => Alt repr => Pro repr => Tag -> repr (a -> k) k -> Permutation repr k (Maybe a) Source #
defaultTag :: TagConstraint repr a => Tag -> a -> repr (a -> k) k -> Permutation repr k a Source #
requiredTag :: TagConstraint repr a => Tag -> repr (a -> k) k -> Permutation repr k a Source #
many0Tag :: TagConstraint repr a => AltApp repr => Tag -> repr (a -> k) k -> Permutation repr k [a] Source #
many1Tag :: TagConstraint repr a => AltApp repr => Tag -> repr (a -> k) k -> Permutation repr k [a] Source #
tag :: Trans repr => CLI_Tag (UnTrans repr) => Tag -> repr f k -> repr f k Source #
endOpts :: Trans repr => CLI_Tag (UnTrans repr) => repr k k Source #
Instances
Class CLI_Response
class CLI_Response repr where Source #
Nothing
type ResponseConstraint repr a :: Constraint Source #
type ResponseArgs repr a :: * Source #
response' :: ResponseConstraint repr a => repr (ResponseArgs repr a) (Response repr) Source #
response' :: forall a. Trans repr => CLI_Response (UnTrans repr) => ResponseConstraint (UnTrans repr) a => ResponseArgs repr a ~ ResponseArgs (UnTrans repr) a => Response repr ~ Response (UnTrans repr) => repr (ResponseArgs repr a) (Response repr) Source #
Instances
response :: forall a repr. CLI_Response repr => ResponseConstraint repr a => repr (ResponseArgs repr a) (Response repr) Source #
Class CLI_Help
class CLI_Help repr where Source #
Nothing
type HelpConstraint repr d :: Constraint Source #
help :: HelpConstraint repr d => d -> repr f k -> repr f k infixr 0 Source #
program :: Name -> repr f k -> repr f k Source #
rule :: Name -> repr f k -> repr f k Source #
program :: Trans repr => CLI_Help (UnTrans repr) => Name -> repr f k -> repr f k Source #
rule :: Trans repr => CLI_Help (UnTrans repr) => Name -> repr f k -> repr f k Source #