Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines the Shaped
typeclass, which is used to generically
manipulate values as fixed-points of higher-order functors in order to
analyze their structure, e.g. while observing evaluation.
If you just care about testing the strictness of functions over datatypes
which are already instances of Shaped
, you don't need to use this module.
Important note: To define new instances of Shaped
for types which
implement Generic
, an empty instance will suffice, as all the
methods of Shaped
can be filled in by generic implementations. For
example:
import GHC.Generics as GHC import Generics.SOP as SOP data D = C deriving (GHC.Generic) instance SOP.Generic D instance SOP.HasDatatypeInfo D instance Shaped D
Using the DeriveAnyClass
extension, this can be shortened to one line:
data D = C deriving (GHC.Generic, SOP.Generic, SOP.HasDatatypeInfo, Shaped)
Manual instances of Shaped
are necessary for types which do not or cannot
implement GHC's Generic
typeclass, such as existential types, abstract
types, and GADTs.
This module is heavily based upon the approach in Data.Functor.Foldable, which in turn is modeled after the paper "Functional Programming with Bananas, Lenses, Envelopes and Barbed Wire" (1991) by Erik Meijer, Maarten Fokkinga and Ross Paterson. If you don't yet understand recursion schemes and want to understand this module, it's probably a good idea to familiarize yourself with Data.Functor.Foldable before diving into this higher-order generalization.
- class Typeable a => Shaped (a :: *) where
- module Test.StrictCheck.Shaped.Flattened
- newtype (f :: * -> *) % (a :: *) :: * where
- unwrap :: (f % a) -> f (Shape a ((%) f))
- interleave :: (Functor f, Shaped a) => (forall x. x -> f x) -> a -> f % a
- (%) :: forall a f. (Functor f, Shaped a) => (forall x. x -> f x) -> a -> f % a
- fuse :: (Functor f, Shaped a) => (forall x. f x -> x) -> (f % a) -> a
- translate :: forall a f g. Shaped a => (forall x. Shaped x => f x -> g x) -> Shape a f -> Shape a g
- fold :: forall a f g. (Functor f, Shaped a) => (forall x. Shaped x => f (Shape x g) -> g x) -> (f % a) -> g a
- unfold :: forall a f g. (Functor g, Shaped a) => (forall x. Shaped x => f x -> g (Shape x f)) -> f a -> g % a
- unzipWith :: (All Functor [f, g, h], Shaped a) => (forall x. f x -> (g x, h x)) -> (f % a) -> (g % a, h % a)
- type QName = (ModuleName, DatatypeName, String)
- data Rendered f = RWrap (f (RenderLevel (Rendered f)))
- data RenderLevel x
- renderfold :: forall a f. (Shaped a, Functor f) => (f % a) -> Rendered f
- newtype Prim (x :: *) (f :: * -> *) = Prim x
- unPrim :: Prim x f -> x
- projectPrim :: (forall x. Shaped x => x -> f x) -> a -> Prim a f
- embedPrim :: (forall x. Shaped x => f x -> x) -> Prim a f -> a
- matchPrim :: Eq a => Prim a f -> Prim a g -> (forall xs. All Shaped xs => Flattened (Prim a) f xs -> Maybe (Flattened (Prim a) g xs) -> result) -> result
- flatPrim :: a -> Flattened (Prim a) g '[]
- renderPrim :: Show a => Prim a (K x) -> RenderLevel x
- renderConstant :: String -> RenderLevel x
- newtype Containing h a f = Container (h (f a))
- projectContainer :: (Functor c, Shaped a) => (forall x. Shaped x => x -> f x) -> c a -> Containing c a f
- embedContainer :: (Functor c, Shaped a) => (forall x. Shaped x => f x -> x) -> Containing c a f -> c a
- type GShaped a = (Generic a, Shape a ~ GShape a, All2 Shaped (Code a), SListI (Code a), All SListI (Code a))
- newtype GShape a f = GS (NS (NP f) (Code a))
- gProject :: GShaped a => (forall x. Shaped x => x -> f x) -> a -> Shape a f
- gEmbed :: GShaped a => (forall x. Shaped x => f x -> x) -> Shape a f -> a
- gMatch :: forall a f g result. GShaped a => Shape a f -> Shape a g -> (forall xs. All Shaped xs => Flattened (Shape a) f xs -> Maybe (Flattened (Shape a) g xs) -> result) -> result
- gRender :: forall a x. (HasDatatypeInfo a, GShaped a) => Shape a (K x) -> RenderLevel x
Documentation
class Typeable a => Shaped (a :: *) where Source #
When a type a
is Shaped
, we know how to convert it into a
representation parameterized by an arbitrary functor f
, so that Shape a f
(the "shape of a
parameterized by f
") is structurally identical to the
topmost structure of a
, but with f
wrapped around any subfields of a
.
Note that this is not a recursive representation! The functor f
in
question wraps the original type of the field and not a Shape
of that
field.
For instance, the Shape
of Either a b
might be:
data EitherShape a b f = LeftShape (f a) | RightShape (f b) instance Shaped (Either a b) where type Shape (Either a b) = EitherShape a b ...
The shape of a primitive type should be isomorphic to the primitive type, with the functor parameter left unused.
type Shape a :: (* -> *) -> * Source #
The Shape
of an a
is a type isomorphic to the outermost level of
structure in an a
, parameterized by the functor f
, which is wrapped
around any fields (of any type) in the original a
.
project :: (forall x. Shaped x => x -> f x) -> a -> Shape a f Source #
Given a function to expand any Shaped
x
into an f x
, expand an a
into a Shape a f
That is: convert the top-most level of structure in the given a
into a
Shape
, calling the provided function on each field in the a
to produce
the f x
necessary to fill that hole in the produced Shape a f
.
Inverse to embed
.
project :: GShaped a => (forall x. Shaped x => x -> f x) -> a -> Shape a f Source #
Given a function to expand any Shaped
x
into an f x
, expand an a
into a Shape a f
That is: convert the top-most level of structure in the given a
into a
Shape
, calling the provided function on each field in the a
to produce
the f x
necessary to fill that hole in the produced Shape a f
.
Inverse to embed
.
embed :: (forall x. Shaped x => f x -> x) -> Shape a f -> a Source #
Given a function to collapse any f x
into a Shaped
x
, collapse a
Shape a f
into merely an a
That is: eliminate the top-most Shape
by calling the provided function on
each field in that Shape a f
, and using the results to fill in the pieces
necessary to build an a
.
Inverse to project
.
embed :: GShaped a => (forall x. Shaped x => f x -> x) -> Shape a f -> a Source #
Given a function to collapse any f x
into a Shaped
x
, collapse a
Shape a f
into merely an a
That is: eliminate the top-most Shape
by calling the provided function on
each field in that Shape a f
, and using the results to fill in the pieces
necessary to build an a
.
Inverse to project
.
match :: Shape a f -> Shape a g -> (forall xs. All Shaped xs => Flattened (Shape a) f xs -> Maybe (Flattened (Shape a) g xs) -> result) -> result Source #
Given two Shape
s of the same type a
but parameterized by potentially
different functors f
and g
, pattern-match on them to expose a uniform
view on their fields (a Flattened
(Shape a)
) to a continuation which
may operate on those fields to produce some result
If the two supplied Shape
s do not structurally match, only the fields of
the first are given to the continuation. If they do match, the fields of
the second are also given, along with type-level proof that the types of
the two sets of fields align.
This very general operation subsumes equality testing, mapping, zipping,
shrinking, and many other structural operations over Shaped
things.
It is somewhat difficult to manually write instances for this method, but
consulting its generic implementation gMatch
may prove helpful.
See Test.StrictCheck.Shaped.Flattened for more information.
match :: GShaped a => Shape a f -> Shape a g -> (forall xs. All Shaped xs => Flattened (Shape a) f xs -> Maybe (Flattened (Shape a) g xs) -> result) -> result Source #
Given two Shape
s of the same type a
but parameterized by potentially
different functors f
and g
, pattern-match on them to expose a uniform
view on their fields (a Flattened
(Shape a)
) to a continuation which
may operate on those fields to produce some result
If the two supplied Shape
s do not structurally match, only the fields of
the first are given to the continuation. If they do match, the fields of
the second are also given, along with type-level proof that the types of
the two sets of fields align.
This very general operation subsumes equality testing, mapping, zipping,
shrinking, and many other structural operations over Shaped
things.
It is somewhat difficult to manually write instances for this method, but
consulting its generic implementation gMatch
may prove helpful.
See Test.StrictCheck.Shaped.Flattened for more information.
render :: Shape a (K x) -> RenderLevel x Source #
Convert a Shape a
whose fields are some unknown constant type into a
RenderLevel
filled with that type
This is a specialized pretty-printing mechanism which allows for displaying
counterexamples in a structured format. See the documentation for
RenderLevel
.
render :: (GShaped a, HasDatatypeInfo a) => Shape a (K x) -> RenderLevel x Source #
Convert a Shape a
whose fields are some unknown constant type into a
RenderLevel
filled with that type
This is a specialized pretty-printing mechanism which allows for displaying
counterexamples in a structured format. See the documentation for
RenderLevel
.
Fixed-points of Shape
s
newtype (f :: * -> *) % (a :: *) :: * where Source #
A value of type f % a
has the same structure as an a
, but with the
structure of the functor f
interleaved at every field (including ones of
types other than a
). Read this type aloud as "a interleaved with f's".
Folds and unfolds over fixed-points of Shape
s
unwrap :: (f % a) -> f (Shape a ((%) f)) Source #
Look inside a single level of an interleaved f % a
. Inverse to the Wrap
constructor.
interleave :: (Functor f, Shaped a) => (forall x. x -> f x) -> a -> f % a Source #
Interleave an f
-structure at every recursive level of some a
, given
some way of generating a single level of structure x -> f x
.
This is a special case of unfold
.
(%) :: forall a f. (Functor f, Shaped a) => (forall x. x -> f x) -> a -> f % a Source #
An infix synonym for interleave
fuse :: (Functor f, Shaped a) => (forall x. f x -> x) -> (f % a) -> a Source #
Fuse the interleaved f
-structure out of a recursively interleaved f %
a
, given some way of fusing a single level f x -> x
.
This is a special case of fold
.
translate :: forall a f g. Shaped a => (forall x. Shaped x => f x -> g x) -> Shape a f -> Shape a g Source #
Map a function across all the fields in a Shape
This function may change the functor over which the Shape
is parameterized.
It can assume recursively that all the fields in the Shape
are themselves
instances of Shaped
(which they should be!). This means that you can nest
calls to translate
recursively.
fold :: forall a f g. (Functor f, Shaped a) => (forall x. Shaped x => f (Shape x g) -> g x) -> (f % a) -> g a Source #
The equivalent of a fold (catamorphism) over recursively Shaped
values
Given a function which folds an f
containing some Shape x g
into a g x
,
recursively fold any interleaved f % a
into a g a
.
unfold :: forall a f g. (Functor g, Shaped a) => (forall x. Shaped x => f x -> g (Shape x f)) -> f a -> g % a Source #
The equivalent of an unfold (anamorphism) over recursively Shaped
values
Given a function which unfolds an f x
into a g
containing some Shape x
f
, corecursively unfold any f a
into an interleaved g % a
.
unzipWith :: (All Functor [f, g, h], Shaped a) => (forall x. f x -> (g x, h x)) -> (f % a) -> (g % a, h % a) Source #
A higher-kinded unzipWith
, operating over interleaved structures
Given a function splitting some f x
into a functor-product Product g h x
,
recursively split an interleaved f % a
into two interleaved structures:
one built of g
-shapes and one of h
-shapes.
Note that Product ((%) g) ((%) h) a
is isomorphic to (g % a, h % a)
; to
get the latter, pattern-match on the Pair
constructor of Product
.
Rendering Shaped
things as structured text
type QName = (ModuleName, DatatypeName, String) Source #
A QName
is a qualified name
Note: > type ModuleName = String > type DatatypeName = String
Rendered f
is the fixed-point of f
composed with RenderLevel
: it
alternates between f
shapes and RenderLevel
s. Usually, f
will be the
identity functor I
, but not always.
RWrap (f (RenderLevel (Rendered f))) |
data RenderLevel x Source #
RenderLevel
is a functor whose outer shape contains all the information
about how to pretty-format the outermost Shape
of some value. We use
parametricity to make it difficult to construct incorrect render
methods,
by asking the user merely to produce a single RenderLevel
and stitching
nested RenderLevel
s into complete Rendered
trees.
ConstructorD QName [x] | A prefix constructor, and a list of its fields |
InfixD QName Associativity Fixity x x | An infix constructor, its associativity and fixity, and its two fields |
RecordD QName [(QName, x)] | A record constructor, and a list of its field names paired with fields |
CustomD Fixity [Either (Either String (ModuleName, String)) (Fixity, x)] | A custom pretty-printing representation (i.e. for abstract types), which records a fixity and a list of tokens of three varieties: 1) raw strings, 2) qualified strings (from some module), or 3) actual fields, annotated with their fixity |
Functor RenderLevel Source # | |
Eq x => Eq (RenderLevel x) Source # | |
Ord x => Ord (RenderLevel x) Source # | |
Show x => Show (RenderLevel x) Source # | |
renderfold :: forall a f. (Shaped a, Functor f) => (f % a) -> Rendered f Source #
TODO: document this strange function
Convert an f % a
into a structured pretty-printing representation,
suitable for further display/processing
Tools for manually writing instances of Shaped
Implementing Shaped
for primitive types
newtype Prim (x :: *) (f :: * -> *) Source #
The Shape
of a primitive type should be equivalent to the type itself.
However, this does not have the right kind to be used as a Shape
.
The Prim
newtype solves this problem. By defining the Shape
of some
primitive type p
to be Prim p
, you can use the methods projectPrim
,
embedPrim
, matchPrim
, and prettyPrim
to completely fill in the
definition of the Shaped
class for a primitive type.
Note: It is only appropriate to use this Shape
representation when a
type really is primitive, in that it contains no interesting substructure.
If you use the Prim
representation inappropriately, StrictCheck will not be
able to inspect the richer structure of the type in question.
Prim x |
unPrim :: Prim x f -> x Source #
Get the wrapped x
out of a Prim x f
(inverse to the Prim
constructor)
projectPrim :: (forall x. Shaped x => x -> f x) -> a -> Prim a f Source #
Generic implementation of project
for any primitive type whose Shape
is
is represented as a Prim
newtype
embedPrim :: (forall x. Shaped x => f x -> x) -> Prim a f -> a Source #
Generic implementation of embed
for any primitive type whose Shape
is
is represented as a Prim
newtype
matchPrim :: Eq a => Prim a f -> Prim a g -> (forall xs. All Shaped xs => Flattened (Prim a) f xs -> Maybe (Flattened (Prim a) g xs) -> result) -> result Source #
Generic implementation of match
for any primitive type whose Shape
is
is represented as a Prim
newtype with an underlying Eq
instance
flatPrim :: a -> Flattened (Prim a) g '[] Source #
Helper for writing match
instances for primitive types which don't have
Eq
instance
This generates a Flattened
appropriate for using in the implementation of
match
. For more documentation on how to use this, see the documentation of
match
.
renderPrim :: Show a => Prim a (K x) -> RenderLevel x Source #
Generic implementation of render
for any primitive type whose Shape
is
is represented as a Prim
newtype
renderConstant :: String -> RenderLevel x Source #
Given some string
, generate a custom pretty-printing representation which
just shows the string
Implementing Shaped
for container types
newtype Containing h a f Source #
The Shape
of a spine-strict container (i.e. a Map
or Set
) is the same
as a container of demands on its elements. However, this does not have the
right kind to be used as a Shape
.
The Containing
newtype solves this problem. By defining the Shape
of some
container (C a)
to be (C
, you can use the methods
Containing
a)projectContainer
and embedContainer
to implement project
and embed
for your container type (although you will still need to manually define
match
and render
).
Container (h (f a)) |
Eq (h (f a)) => Eq (Containing k2 k1 h a f) Source # | |
Ord (h (f a)) => Ord (Containing k2 k1 h a f) Source # | |
Show (h (f a)) => Show (Containing k2 k1 h a f) Source # | |
projectContainer :: (Functor c, Shaped a) => (forall x. Shaped x => x -> f x) -> c a -> Containing c a f Source #
Generic implementation of project
for any container type whose Shape
is represented as a Containing
newtype
embedContainer :: (Functor c, Shaped a) => (forall x. Shaped x => f x -> x) -> Containing c a f -> c a Source #
Generic implementation of embed
for any container type whose Shape
is represented as a Containing
newtype
Generic implementation of the methods of Shaped
type GShaped a = (Generic a, Shape a ~ GShape a, All2 Shaped (Code a), SListI (Code a), All SListI (Code a)) Source #
The collection of constraints necessary for a type to be given a generic
implementation of the Shaped
methods
The Shape
used for generic implementations of Shaped
This wraps a sum-of-products representation from Generics.SOP.
gMatch :: forall a f g result. GShaped a => Shape a f -> Shape a g -> (forall xs. All Shaped xs => Flattened (Shape a) f xs -> Maybe (Flattened (Shape a) g xs) -> result) -> result Source #
Generic match
gRender :: forall a x. (HasDatatypeInfo a, GShaped a) => Shape a (K x) -> RenderLevel x Source #
Generic render