{- - Copyright (C) 2019 Koz Ross - - This program is free software: you can redistribute it and/or modify - it under the terms of the GNU General Public License as published by - the Free Software Foundation, either version 3 of the License, or - (at your option) any later version. - - This program is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the - GNU General Public License for more details. - - You should have received a copy of the GNU General Public License - along with this program. If not, see . -} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Data.Finitary.TH where import Foreign.Storable (Storable, sizeOf) import Language.Haskell.TH (Q, Type(..), TyLit(..), Exp(..), Lit(..)) charCardinality :: Q Type charCardinality = pure . LitT . NumTyLit . fromIntegral . (+ 1) . fromEnum $ maxBound @Char cardinalityOf :: forall a . (Storable a) => Q Type cardinalityOf = pure . LitT . NumTyLit . product . replicate (sizeOf @a undefined * 8) $ 2 adjustmentOf :: forall a . (Integral a, Bounded a) => Q Exp adjustmentOf = pure . LitE . IntegerL . (+ 1) . fromIntegral @_ @Integer $ maxBound @a