% Extensible lists % [Public domain] \input birdstyle \birdleftrule=1pt \emergencystretch=1em \def\hugebreak{\penalty-600\vskip 30pt plus 8pt minus 4pt\relax} \newcount\chapno \def\: #1.{\advance\chapno by 1\relax\hugebreak{\bf\S\the\chapno. #1. }} \: Introduction. This module implements extensible lists. The values in the list can be extensible even in other modules. NB: In order to use this module, you need to enable the {\tt ScopedTypeVariables} extension, because it generates patterns with type signatures. > {-# LANGUAGE MultiParamTypeClasses, TemplateHaskell #-} > {-# LANGUAGE FunctionalDependencies #-} > module Data.Extensible.List ( > ExtList(..), extList > ) where { > import Control.Applicative; > import Control.Monad; > import Data.List; > import Language.Haskell.TH; \: Utility Function. > bool :: x -> x -> Bool -> x; > bool x _ False = x; > bool _ x True = x; \: Implementation. The implementation is a class; its instances represent the values to add to the list. Its only method, {\tt extListContents}, should specify the list of values to include. The value of the first part of the pair is irrelevant; it is only used to keep track of the type. > class ExtList v p | p -> v where { > extListContents :: (p, [v]); > }; The following is the TH splicer function; it is given a name of a type which is the {\tt v} parameter of the class above, and produces an expression which evaluates into the list of all values of all instances that have that {\tt v} which are in scope (example: {\tt\$(extList ''List1)}). There is no guarantee to the ordering of the values, except that values in a single instance will be in the same order relative to each other and contiguous. > extList :: Name -> Q Exp; > extList x = liftM2 (\n (ClassI _ i) -> extListInst n (ConT x) i) > (newName "x") (reify ''ExtList); > extListInst :: Name -> Type -> [ClassInstance] -> Exp; > extListInst _ _ [] = ListE []; > extListInst n x (ClassInstance { ci_tys = [v, p] } : t) = bool id > (InfixE (Just e) (VarE '(++)) . Just) (v == x) (extListInst n x t) > where { > e :: Exp; > e = AppE (LamE [ConP '(,) [SigP WildP p, VarP n]] $ VarE n) > (VarE 'extListContents); > }; % End of document (final "}" is suppressed from printout) \medskip\centerline{The End} \toks0={{ > } -- }\bye