{-# LANGUAGE TemplateHaskell #-} {- | Module : Type.Digits.Stage0 Copyright : (c) The University of Kansas 2011 License : BSD3 Maintainer : nicolas.frisby@gmail.com Stability : experimental Portability : see LANGUAGE pragmas (... GHC) Type-level numerals built from type-level digits of an arbitrary radix. -} module Type.Digits.Stage0 where import Type.Digits.Aux import Language.Haskell.TH import Control.Monad (ap) -- declares each digit (: []) `fmap` dataD (cxt []) (mkName "Digit") [] (normalC (mkName "DigitStop") [] : [ normalC n [(,) `fmap` notStrict `ap` conT (mkName "Digit")] | n <- map mkName digitStrings ] ) []