generic-data-functions-0.6.0: Familiar functions lifted to generic data types
Safe HaskellSafe-Inferred
LanguageGHC2021

Generic.Data.MetaParse.Cstr

Description

Definitions for parsing data type constructor names on the type level.

Classically, when doing Generic programming in Haskell that inspects data type metadata such as constructor and record names, we reify these early and do any parsing etc. on the term level. Constant folding should compute much of this at compile time, so performance isn't really a worry. But if you're doing failable operations such as parsing, you can't catch failures at compile time.

This module provides definitions for parsing constructor names on the type level, and is used internally in sum type generics. But wait, how do you write a type-level string parser? That's now feasible-- see the Symparsec library :)

Synopsis

Documentation

class CstrParser' tag => CstrParser tag Source #

Types defining constructor name parsers.

When defining instances of these two classes, ensure that you place an empty TH splice e.g. $(pure []) between the instances. This is due to a GHC bug.

Associated Types

type ParseCstr tag (str :: Symbol) :: Either ErrorMessage (CstrParseResult tag) Source #

Constructor name parser.

The Symparsec library generates type families that look like this. See Generic.Data.Cstr.Parser.Symparsec for handy definitions.

type ReifyCstrParseResult tag (x :: CstrParseResult tag) :: Constraint Source #

Constraint enabling reification of the parsed type-level constructor name.

For example, you might reify '(a, b) :: (Symbol, Symbol) with (KnownSymbol a, KnownSymbol b).

Instances

Instances details
CstrParser Raw Source # 
Instance details

Defined in Generic.Data.MetaParse.Cstr

class CstrParser' tag Source #

Types defining constructor name parsers (inner class).

We're forced to separate this associated type family from the other class due to GHC complaining "type constructor cannot be used here (it is defined and used in the same recursive group)".

When defining instances of these two classes, ensure that you place an empty TH splice e.g. $(pure []) between the instances. This is due to a GHC bug.

Associated Types

type CstrParseResult tag :: k Source #

Result kind of the constructor name parser.

Instances

Instances details
CstrParser' Raw Source # 
Instance details

Defined in Generic.Data.MetaParse.Cstr

Associated Types

type CstrParseResult Raw :: k1 Source #

type family ForceGCParse dtName cstr a where ... Source #

Unwrap a generic constructor parse result. Emits a TypeError on parse failure.

Equations

ForceGCParse _ _ (Right a) = a 
ForceGCParse dtName cstr (Left e) = TypeError (((((Text "error while parsing " :<>: Text dtName) :<>: Text ".") :<>: Text cstr) :<>: Text ":") :$$: e) 

data Raw Source #

Type-level parser tag. Return the string unparsed.

Instances

Instances details
CstrParser Raw Source # 
Instance details

Defined in Generic.Data.MetaParse.Cstr

CstrParser' Raw Source # 
Instance details

Defined in Generic.Data.MetaParse.Cstr

Associated Types

type CstrParseResult Raw :: k1 Source #

type CstrParseResult Raw Source # 
Instance details

Defined in Generic.Data.MetaParse.Cstr

type ParseCstr Raw str Source # 
Instance details

Defined in Generic.Data.MetaParse.Cstr

type ReifyCstrParseResult Raw (str :: CstrParseResult Raw :: Type) Source # 
Instance details

Defined in Generic.Data.MetaParse.Cstr

type ParseCstrTo tag r = forall (x :: CstrParseResult tag). ReifyCstrParseResult tag x => Proxy# x -> r Source #

Constructor name parse result demotion function using Proxy#.