getopt-generics-0.11.0.1: Create command line interfaces with ease

Safe HaskellNone
LanguageHaskell2010

System.Console.GetOpt.Generics

Contents

Synopsis

Simple IO API

withCli :: forall main. WithCli main => main -> IO () Source

withCli 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 instances for HasArguments.

May throw the following exceptions:

  • ExitFailure 1 in case of invalid options. Error messages are written to stderr.
  • ExitSuccess in case --help is given. (ExitSuccess behaves like a normal exception, except that -- if uncaught -- the process will exit with exit-code 0.) Help output is written to stdout.

Example:

 import WithCli

 main :: IO ()
 main = withCli run

 run :: String -> Int -> Bool -> IO ()
 run s i b = print (s, i, b)

Using the above program in a shell:

 $ program foo 42 true
 ("foo",42,True)
 $ program --help
 program [OPTIONS] STRING INTEGER BOOL
   -h  --help  show help and exit
 $ program foo 42 bar
 cannot parse as BOOL: bar
 # exit-code 1
 $ program
 missing argument of type STRING
 missing argument of type INTEGER
 missing argument of type BOOL
 # exit-code 1
 $ program foo 42 yes bar
 unknown argument: bar
 # exit-code 1

class WithCli main Source

Everything that can be used as a main function with withCli needs to have an instance of WithCli. You shouldn't need to implement your own instances.

Instances

WithCli (IO ()) Source 
(HasArguments a, WithCli rest) => WithCli (a -> rest) Source 

class HasArguments a Source

Everything that can be used as an argument to your main function (see withCli) needs to have a HasArguments instance.

HasArguments also allows to conjure up instances for record types to create more complex command line interfaces. Here's an example:

 {-# LANGUAGE DeriveGeneric #-}

 import qualified GHC.Generics
 import           System.Console.GetOpt.Generics

 data Options
   = Options {
     port :: Int,
     daemonize :: Bool,
     config :: Maybe FilePath
   }
   deriving (Show, GHC.Generics.Generic)

 instance Generic Options
 instance HasDatatypeInfo Options
 instance HasArguments Options

 main :: IO ()
 main = withCli run

 run :: Options -> IO ()
 run = print

In a shell this program behaves like this:

 $ 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
 # exit-code 1
 $ program
 missing option: --port=INTEGER
 # exit-code 1
 $ program --help
 program [OPTIONS]
       --port=INTEGER
       --daemonize
       --config=STRING (optional)
   -h  --help                      show help and exit

class Argument a where Source

Argument is a typeclass for things that can be parsed as atomic values from single command line arguments, e.g. strings (and filenames) and numbers.

Occasionally you might want to declare your own instance for additional type safety and for providing a more informative command argument type. Here's an example:

 {-# LANGUAGE DeriveDataTypeable #-}

 import WithCli

 data File = File FilePath
   deriving (Show, Typeable)

 instance Argument File where
   argumentType Proxy = "custom-file-type"
   parseArgument f = Just (File f)

 instance HasArguments File where
   argumentsParser = atomicArgumentsParser

 main :: IO ()
 main = withCli run

 run :: File -> IO ()
 run = print

And this is how the above program behaves:

 $ program --help
 program [OPTIONS] custom-file-type
   -h  --help  show help and exit
 $ program some/file
 File "some/file"

Customizing the CLI

withCliModified :: forall main. WithCli main => [Modifier] -> main -> IO () Source

This is a variant of withCli that allows to tweak the generated command line interface by providing a list of Modifiers.

data Modifier Source

Modifiers can be used to customize the command line parser.

Constructors

AddShortOption String Char

AddShortOption fieldName c adds the Char c as a short option for the field addressed by fieldName.

RenameOption String String

RenameOption fieldName customName renames the option generated through the fieldName by customName.

RenameOptions (String -> Maybe String)

RenameOptions f renames all options with the given functions. In case the function returns Nothing the original field name is used.

Can be used together with stripPrefix.

UseForPositionalArguments String String

UseForPositionalArguments fieldName argumentType fills the field addressed by fieldName with the positional arguments (i.e. arguments that don't correspond to a flag). The field has to have type [String].

argumentType is used as the type of the positional arguments in the help output.

AddOptionHelp String String

AddOptionHelp fieldName helpText adds a help text for the option fieldName.

AddVersionFlag String

AddVersionFlag version adds a --version flag.

IO API

getArguments :: forall a. (Generic a, HasDatatypeInfo a, All2 HasArguments (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 withCli.

Here's an example:

 {-# LANGUAGE DeriveGeneric #-}

 module RecordType where

 import qualified 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 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
 # exit-code 1
 $ program
 missing option: --port=INTEGER
 # exit-code 1
 $ program --help
 program [OPTIONS]
       --port=INTEGER
       --daemonize
       --config=STRING (optional)
   -h  --help                      show help and exit

modifiedGetArguments :: forall a. (Generic a, HasDatatypeInfo a, All2 HasArguments (Code a)) => [Modifier] -> IO a Source

Like getArguments but allows you to pass in Modifiers.

Pure API

parseArguments Source

Arguments

:: (Generic a, HasDatatypeInfo a, All2 HasArguments (Code a)) 
=> String

Name of the program (e.g. from getProgName).

-> [Modifier]

List of Modifiers to manually tweak the command line interface.

-> [String]

List of command line arguments to parse (e.g. from getArgs).

-> Result a 

Pure variant of modifiedGetArguments.

Does not throw any exceptions.

data Result a Source

Type to wrap results from the pure parsing functions.

Constructors

Success a

The CLI was used correctly and a value of type a was successfully constructed.

Errors [String]

The CLI was used incorrectly. The Result contains a list of error messages.

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 --help. The Result contains the help message.

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 -> a
from . 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, ...)

instance Generic T -- empty
instance HasDatatypeInfo 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 -- derives HasDatatypeInfo 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.

Associated Types

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 ]
   ]

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 ]
   ]

Instances

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 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 GeneralCategory = (:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ((:) [*] ([] *) ([] [*])))))))))))))))))))))))))))))) 
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.

Instances

type All2 k c ([] [k]) = () 
type All2 k c ((:) [k] x xs) = (All k c x, All2 k c xs)