Safe Haskell | None |
---|---|
Language | Haskell2010 |
- simpleCLI :: forall main. (SimpleCLI main, All Option (ArgumentTypes main)) => main -> IO ()
- class SingI (ArgumentTypes main) => SimpleCLI main where
- type ArgumentTypes main :: [*]
- getArguments :: forall a. (Generic a, HasDatatypeInfo a, All2 Option (Code a)) => IO a
- modifiedGetArguments :: forall a. (Generic a, HasDatatypeInfo a, All2 Option (Code a)) => [Modifier] -> IO a
- parseArguments :: forall a. (Generic a, HasDatatypeInfo a, All2 Option (Code a)) => String -> [Modifier] -> [String] -> Result a
- data Result a
- = Success a
- | Errors [String]
- | OutputAndExit String
- data Modifier
- deriveShortOptions :: (HasDatatypeInfo a, SingI (Code a)) => Proxy a -> [Modifier]
- class Typeable a => Option a where
- argumentType :: Proxy a -> String
- parseArgument :: String -> Maybe a
- class (SingI [[*]] (Code a), All [*] (SingI [*]) (Code a)) => Generic a where
- type Code a :: [[*]]
- class HasDatatypeInfo a
- type family Code a :: [[*]]
- type family All2 c xs :: Constraint
- class SingI a
- data Proxy t :: k -> * = Proxy
IO API
simpleCLI :: forall main. (SimpleCLI main, All Option (ArgumentTypes main)) => main -> IO () Source
simpleCLI
converts an IO operation into a program with a proper CLI.
Retrieves command line arguments through withArgs
.
main
(the given IO operation) can have arbitrarily many parameters
provided all parameters have an instance for Option
.
May throw the following exceptions:
in case of invalid options. Error messages are written toExitFailure
1stderr
.
in caseExitSuccess
--help
is given. (
behaves like a normal exception, except that -- if uncaught -- the process will exit with exit-codeExitSuccess
0
.) Help output is written tostdout
.
Example:
import System.Console.GetOpt.Generics main :: IO () main = simpleCLI myMain myMain :: String -> Int -> Bool -> IO () myMain s i b = print (s, i, b)
Using the above program in bash:
$ program foo 42 true ("foo",42,True) $ program foo 42 bar cannot parse as BOOL: bar $ program --help program [OPTIONS] STRING INTEGER BOOL -h --help show help and exit
class SingI (ArgumentTypes main) => SimpleCLI main Source
_initialFieldStates, _run
type ArgumentTypes main :: [*] Source
getArguments :: forall a. (Generic a, HasDatatypeInfo a, All2 Option (Code a)) => IO a Source
Parses command line arguments (gotten from withArgs
) and returns the
parsed value. This function should be enough for simple use-cases.
Throws the same exceptions as simpleCLI
.
Here's an example:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics import System.Console.GetOpt.Generics -- All you have to do is to define a type and derive some instances: data Options = Options { port :: Int, daemonize :: Bool, config :: Maybe FilePath } deriving (Show, GHC.Generics.Generic) instance System.Console.GetOpt.Generics.Generic Options instance HasDatatypeInfo Options -- Then you can use `getArguments` to create a command-line argument parser: main :: IO () main = do options <- getArguments print (options :: Options)
And this is how the above program behaves:
$ program --port 8080 --config some/path Options {port = 8080, daemonize = False, config = Just "some/path"} $ program --port 8080 --daemonize Options {port = 8080, daemonize = True, config = Nothing} $ program --port foo cannot parse as INTEGER: foo $ program missing option: --port=INTEGER $ program --help program [OPTIONS] --port=INTEGER --daemonize --config=STRING (optional) -h --help show help and exit
modifiedGetArguments :: forall a. (Generic a, HasDatatypeInfo a, All2 Option (Code a)) => [Modifier] -> IO a Source
Like getArguments
but allows you to pass in Modifier
s.
Pure API
:: (Generic a, HasDatatypeInfo a, All2 Option (Code a)) | |
=> String | Name of the program (e.g. from |
-> [Modifier] | List of |
-> [String] | List of command line arguments to parse (e.g. from |
-> Result a |
Pure variant of modifiedGetArguments
.
Does not throw any exceptions.
Type to wrap results from the pure parsing functions.
Success a | The CLI was used correctly and a value of type |
Errors [String] | The CLI was used incorrectly. The It can also happen that the data type you're trying to use isn't supported. See the README for details. |
OutputAndExit String | The CLI was used with |
Customizing the CLI
Modifier
s can be used to customize the command line parser.
AddShortOption String Char |
|
RenameOption String String |
|
RenameOptions (String -> Maybe String) |
Can be used together with |
UseForPositionalArguments String String |
|
AddOptionHelp String String |
|
AddVersionFlag String |
|
deriveShortOptions :: (HasDatatypeInfo a, SingI (Code a)) => Proxy a -> [Modifier] Source
Derives AddShortOption
s for all fields of the datatype that start with a
unique character.
Available Field Types
class Typeable a => Option a where Source
Type class for all allowed field types.
If you want to use custom field types you should implement an
instance Option YourCustomType
containing implementations of
argumentType
and parseArgument
(the minimal complete definition).
Here's an example:
{-# LANGUAGE DeriveDataTypeable #-} import Data.Typeable import System.Console.GetOpt.Generics data File = File FilePath deriving (Show, Typeable) instance Option File where argumentType Proxy = "custom-file-type" parseArgument f = Just (File f) main :: IO () main = simpleCLI $ \ file -> do print (file :: File)
This would give you:
$ program some/file File "some/file" $ program --help program [OPTIONS] custom-file-type -h --help show help and exit
argumentType :: Proxy a -> String Source
Name of the argument type, e.g. "bool" or "integer".
parseArgument :: String -> Maybe a Source
Re-exports from Generics.SOP
class (SingI [[*]] (Code a), All [*] (SingI [*]) (Code a)) => Generic a
The class of representable datatypes.
The SOP approach to generic programming is based on viewing
datatypes as a representation (Rep
) built from the sum of
products of its components. The components of are datatype
are specified using the Code
type family.
The isomorphism between the original Haskell datatype and its
representation is witnessed by the methods of this class,
from
and to
. So for instances of this class, the following
laws should (in general) hold:
to
.
from
===id
:: a -> afrom
.
to
===id
::Rep
a ->Rep
a
You typically don't define instances of this class by hand, but rather derive the class instance automatically.
Option 1: Derive via the built-in GHC-generics. For this, you
need to use the DeriveGeneric
extension to first derive an
instance of the Generic
class from module GHC.Generics.
With this, you can then give an empty instance for Generic
, and
the default definitions will just work. The pattern looks as
follows:
import qualified GHC.Generics as GHC import Generics.SOP ... data T = ... deriving (GHC.Generic
, ...) instanceGeneric
T -- empty instanceHasDatatypeInfo
T -- empty, if you want/need metadata
Option 2: Derive via Template Haskell. For this, you need to
enable the TemplateHaskell
extension. You can then use
deriveGeneric
from module Generics.SOP.TH
to have the instance generated for you. The pattern looks as
follows:
import Generics.SOP import Generics.SOP.TH ... data T = ...deriveGeneric
''T -- derivesHasDatatypeInfo
as well
Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.
Non-standard instances:
It is possible to give Generic
instances manually that deviate
from the standard scheme, as long as at least
to
.
from
===id
:: a -> a
still holds.
type Code a :: [[*]]
The code of a datatype.
This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).
Example: The datatype
data Tree = Leaf Int | Node Tree Tree
is supposed to have the following code:
type instance Code (Tree a) = '[ '[ Int ] , '[ Tree, Tree ] ]
Generic Bool | |
Generic Ordering | |
Generic () | |
Generic FormatAdjustment | |
Generic FormatSign | |
Generic FieldFormat | |
Generic FormatParse | |
Generic DataRep | |
Generic ConstrRep | |
Generic Fixity | |
Generic Version | |
Generic IOMode | |
Generic PatternMatchFail | |
Generic RecSelError | |
Generic RecConError | |
Generic RecUpdError | |
Generic NoMethodError | |
Generic NonTermination | |
Generic NestedAtomically | |
Generic Errno | |
Generic BlockedIndefinitelyOnMVar | |
Generic BlockedIndefinitelyOnSTM | |
Generic Deadlock | |
Generic AssertionFailed | |
Generic AsyncException | |
Generic ArrayException | |
Generic ExitCode | |
Generic BufferMode | |
Generic Newline | |
Generic NewlineMode | |
Generic SeekMode | |
Generic GeneralCategory | |
Generic CChar | |
Generic CSChar | |
Generic CUChar | |
Generic CShort | |
Generic CUShort | |
Generic CInt | |
Generic CUInt | |
Generic CLong | |
Generic CULong | |
Generic CLLong | |
Generic CULLong | |
Generic CFloat | |
Generic CDouble | |
Generic CPtrdiff | |
Generic CSize | |
Generic CWchar | |
Generic CSigAtomic | |
Generic CClock | |
Generic CTime | |
Generic CUSeconds | |
Generic CSUSeconds | |
Generic CIntPtr | |
Generic CUIntPtr | |
Generic CIntMax | |
Generic CUIntMax | |
Generic MaskingState | |
Generic IOException | |
Generic ErrorCall | |
Generic ArithException | |
Generic All | |
Generic Any | |
Generic Lexeme | |
Generic Number | |
Generic [a0] | |
Generic (ArgOrder a0) | |
Generic (OptDescr a0) | |
Generic (ArgDescr a0) | |
Generic (Fixed a0) | |
Generic (Complex a0) | |
Generic (Dual a0) | |
Generic (Endo a0) | |
Generic (Sum a0) | |
Generic (Product a0) | |
Generic (First a0) | |
Generic (Last a0) | |
Generic (Down a0) | |
Generic (Maybe a0) | |
Generic (I a0) | |
Generic (Either a0 b0) | |
Generic (a0, b0) | |
Generic (Proxy * t0) | |
Typeable (* -> Constraint) Generic | |
Generic (a0, b0, c0) | |
Generic (K * a0 b0) | |
Generic (a0, b0, c0, d0) | |
Generic (a0, b0, c0, d0, e0) | |
Generic ((:.:) * * f0 g0 p0) | |
Generic (a0, b0, c0, d0, e0, f0) | |
Generic (a0, b0, c0, d0, e0, f0, g0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290, t300) | |
Generic (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290, t300, t310) |
class HasDatatypeInfo a
A class of datatypes that have associated metadata.
It is possible to use the sum-of-products approach to generic programming without metadata. If you need metadata in a function, an additional constraint on this class is in order.
You typically don't define instances of this class by hand, but
rather derive the class instance automatically. See the documentation
of Generic
for the options.
type family Code a :: [[*]]
The code of a datatype.
This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).
Example: The datatype
data Tree = Leaf Int | Node Tree Tree
is supposed to have the following code:
type instance Code (Tree a) = '[ '[ Int ] , '[ Tree, Tree ] ]
type Code Bool = (:) [*] ([] *) ((:) [*] ([] *) ([] [*])) | |
type Code Ordering = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*]))) | |
type Code () = (:) [*] ([] *) ([] [*]) | |
type Code FormatAdjustment = (:) [*] ([] *) ((:) [*] ([] *) ([] [*])) | |
type Code FormatSign = (:) [*] ([] *) ((:) [*] ([] *) ([] [*])) | |
type Code FieldFormat = (:) [*] ((:) * (Maybe Int) ((:) * (Maybe Int) ((:) * (Maybe FormatAdjustment) ((:) * (Maybe FormatSign) ((:) * Bool ((:) * String ((:) * Char ([] *)))))))) ([] [*]) | |
type Code FormatParse = (:) [*] ((:) * String ((:) * Char ((:) * String ([] *)))) ([] [*]) | |
type Code DataRep = (:) [*] ((:) * [Constr] ([] *)) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*]))))) | |
type Code ConstrRep = (:) [*] ((:) * ConIndex ([] *)) ((:) [*] ((:) * Integer ([] *)) ((:) [*] ((:) * Rational ([] *)) ((:) [*] ((:) * Char ([] *)) ([] [*])))) | |
type Code Fixity = (:) [*] ([] *) ((:) [*] ([] *) ([] [*])) | |
type Code Version = (:) [*] ((:) * [Int] ((:) * [String] ([] *))) ([] [*]) | |
type Code IOMode = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*])))) | |
type Code PatternMatchFail = (:) [*] ((:) * String ([] *)) ([] [*]) | |
type Code RecSelError = (:) [*] ((:) * String ([] *)) ([] [*]) | |
type Code RecConError = (:) [*] ((:) * String ([] *)) ([] [*]) | |
type Code RecUpdError = (:) [*] ((:) * String ([] *)) ([] [*]) | |
type Code NoMethodError = (:) [*] ((:) * String ([] *)) ([] [*]) | |
type Code NonTermination = (:) [*] ([] *) ([] [*]) | |
type Code NestedAtomically = (:) [*] ([] *) ([] [*]) | |
type Code Errno = (:) [*] ((:) * CInt ([] *)) ([] [*]) | |
type Code BlockedIndefinitelyOnMVar = (:) [*] ([] *) ([] [*]) | |
type Code BlockedIndefinitelyOnSTM = (:) [*] ([] *) ([] [*]) | |
type Code Deadlock = (:) [*] ([] *) ([] [*]) | |
type Code AssertionFailed = (:) [*] ((:) * String ([] *)) ([] [*]) | |
type Code AsyncException = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*])))) | |
type Code ArrayException = (:) [*] ((:) * String ([] *)) ((:) [*] ((:) * String ([] *)) ([] [*])) | |
type Code ExitCode = (:) [*] ([] *) ((:) [*] ((:) * Int ([] *)) ([] [*])) | |
type Code BufferMode = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ((:) * (Maybe Int) ([] *)) ([] [*]))) | |
type Code Newline = (:) [*] ([] *) ((:) [*] ([] *) ([] [*])) | |
type Code NewlineMode = (:) [*] ((:) * Newline ((:) * Newline ([] *))) ([] [*]) | |
type Code SeekMode = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*]))) | |
type Code GeneralCategory = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*])))))))))))))))))))))))))))))) | |
type Code CChar = (:) [*] ((:) * Int8 ([] *)) ([] [*]) | |
type Code CSChar = (:) [*] ((:) * Int8 ([] *)) ([] [*]) | |
type Code CUChar = (:) [*] ((:) * Word8 ([] *)) ([] [*]) | |
type Code CShort = (:) [*] ((:) * Int16 ([] *)) ([] [*]) | |
type Code CUShort = (:) [*] ((:) * Word16 ([] *)) ([] [*]) | |
type Code CInt = (:) [*] ((:) * Int32 ([] *)) ([] [*]) | |
type Code CUInt = (:) [*] ((:) * Word32 ([] *)) ([] [*]) | |
type Code CLong = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CULong = (:) [*] ((:) * Word64 ([] *)) ([] [*]) | |
type Code CLLong = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CULLong = (:) [*] ((:) * Word64 ([] *)) ([] [*]) | |
type Code CFloat = (:) [*] ((:) * Float ([] *)) ([] [*]) | |
type Code CDouble = (:) [*] ((:) * Double ([] *)) ([] [*]) | |
type Code CPtrdiff = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CSize = (:) [*] ((:) * Word64 ([] *)) ([] [*]) | |
type Code CWchar = (:) [*] ((:) * Int32 ([] *)) ([] [*]) | |
type Code CSigAtomic = (:) [*] ((:) * Int32 ([] *)) ([] [*]) | |
type Code CClock = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CTime = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CUSeconds = (:) [*] ((:) * Word32 ([] *)) ([] [*]) | |
type Code CSUSeconds = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CIntPtr = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CUIntPtr = (:) [*] ((:) * Word64 ([] *)) ([] [*]) | |
type Code CIntMax = (:) [*] ((:) * Int64 ([] *)) ([] [*]) | |
type Code CUIntMax = (:) [*] ((:) * Word64 ([] *)) ([] [*]) | |
type Code MaskingState = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*]))) | |
type Code IOException = (:) [*] ((:) * (Maybe Handle) ((:) * IOErrorType ((:) * String ((:) * String ((:) * (Maybe CInt) ((:) * (Maybe FilePath) ([] *))))))) ([] [*]) | |
type Code ErrorCall = (:) [*] ((:) * String ([] *)) ([] [*]) | |
type Code ArithException = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*])))))) | |
type Code All = (:) [*] ((:) * Bool ([] *)) ([] [*]) | |
type Code Any = (:) [*] ((:) * Bool ([] *)) ([] [*]) | |
type Code Lexeme = (:) [*] ((:) * Char ([] *)) ((:) [*] ((:) * String ([] *)) ((:) [*] ((:) * String ([] *)) ((:) [*] ((:) * String ([] *)) ((:) [*] ((:) * String ([] *)) ((:) [*] ((:) * Number ([] *)) ((:) [*] ([] *) ([] [*]))))))) | |
type Code Number = (:) [*] ((:) * Int ((:) * Digits ([] *))) ((:) [*] ((:) * Digits ((:) * (Maybe Digits) ((:) * (Maybe Integer) ([] *)))) ([] [*])) | |
type Code [a0] = (:) [*] ([] *) ((:) [*] ((:) * a0 ((:) * [a0] ([] *))) ([] [*])) | |
type Code (ArgOrder a0) = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ((:) * (String -> a0) ([] *)) ([] [*]))) | |
type Code (OptDescr a0) = (:) [*] ((:) * [Char] ((:) * [String] ((:) * (ArgDescr a0) ((:) * String ([] *))))) ([] [*]) | |
type Code (ArgDescr a0) = (:) [*] ((:) * a0 ([] *)) ((:) [*] ((:) * (String -> a0) ((:) * String ([] *))) ((:) [*] ((:) * (Maybe String -> a0) ((:) * String ([] *))) ([] [*]))) | |
type Code (Fixed a0) = (:) [*] ((:) * Integer ([] *)) ([] [*]) | |
type Code (Complex a0) = (:) [*] ((:) * a0 ((:) * a0 ([] *))) ([] [*]) | |
type Code (Dual a0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) | |
type Code (Endo a0) = (:) [*] ((:) * (a0 -> a0) ([] *)) ([] [*]) | |
type Code (Sum a0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) | |
type Code (Product a0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) | |
type Code (First a0) = (:) [*] ((:) * (Maybe a0) ([] *)) ([] [*]) | |
type Code (Last a0) = (:) [*] ((:) * (Maybe a0) ([] *)) ([] [*]) | |
type Code (Down a0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) | |
type Code (Maybe a0) = (:) [*] ([] *) ((:) [*] ((:) * a0 ([] *)) ([] [*])) | |
type Code (I a0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) | |
type Code (Either a0 b0) = (:) [*] ((:) * a0 ([] *)) ((:) [*] ((:) * b0 ([] *)) ([] [*])) | |
type Code (a0, b0) = (:) [*] ((:) * a0 ((:) * b0 ([] *))) ([] [*]) | |
type Code (Proxy * t0) = (:) [*] ([] *) ([] [*]) | |
type Code (a0, b0, c0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ([] *)))) ([] [*]) | |
type Code (K * a0 b0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) | |
type Code (a0, b0, c0, d0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ([] *))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ([] *)))))) ([] [*]) | |
type Code ((:.:) * * f0 g0 p0) = (:) [*] ((:) * (f0 (g0 p0)) ([] *)) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ([] *))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ([] *)))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ([] *))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ([] *)))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ([] *))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ([] *)))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ([] *))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ([] *)))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ([] *))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ([] *)))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ([] *))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ([] *)))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ([] *))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ([] *)))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ([] *))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ([] *)))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ([] *))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ([] *)))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ((:) * x0 ([] *))))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ((:) * x0 ((:) * y0 ([] *)))))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ((:) * x0 ((:) * y0 ((:) * z0 ([] *))))))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ((:) * x0 ((:) * y0 ((:) * z0 ((:) * t280 ([] *)))))))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ((:) * x0 ((:) * y0 ((:) * z0 ((:) * t280 ((:) * t290 ([] *))))))))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290, t300) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ((:) * x0 ((:) * y0 ((:) * z0 ((:) * t280 ((:) * t290 ((:) * t300 ([] *)))))))))))))))))))))))))))))) ([] [*]) | |
type Code (a0, b0, c0, d0, e0, f0, g0, h0, i0, j0, k0, l0, m0, n0, o0, p0, q0, r0, s0, t0, u0, v0, w0, x0, y0, z0, t280, t290, t300, t310) = (:) [*] ((:) * a0 ((:) * b0 ((:) * c0 ((:) * d0 ((:) * e0 ((:) * f0 ((:) * g0 ((:) * h0 ((:) * i0 ((:) * j0 ((:) * k0 ((:) * l0 ((:) * m0 ((:) * n0 ((:) * o0 ((:) * p0 ((:) * q0 ((:) * r0 ((:) * s0 ((:) * t0 ((:) * u0 ((:) * v0 ((:) * w0 ((:) * x0 ((:) * y0 ((:) * z0 ((:) * t280 ((:) * t290 ((:) * t300 ((:) * t310 ([] *))))))))))))))))))))))))))))))) ([] [*]) |
type family All2 c xs :: Constraint
Require a constraint for every element of a list of lists.
If you have a datatype that is indexed over a type-level
list of lists, then you can use All2
to indicate that all
elements of the innert lists must satisfy a given constraint.
Example: The constraint
All2 Eq '[ '[ Int ], '[ Bool, Char ] ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All2 Eq xss => SOP I xs -> ...
means that f
can assume that all elements of the sum
of product satisfy Eq
.
class SingI a
data Proxy t :: k -> *
A concrete, poly-kinded proxy type
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Data t => Data (Proxy * t) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy * t) | |
Monoid (Proxy * s) | |
Generic (Proxy * t0) | |
HasDatatypeInfo (Proxy * t0) | |
Typeable (k -> *) (Proxy k) | |
type Rep (Proxy k t) = D1 D1Proxy (C1 C1_0Proxy U1) | |
type Code (Proxy * t0) = (:) [*] ([] *) ([] [*]) |