{-# LANGUAGE TemplateHaskell, DataKinds, PolyKinds, ScopedTypeVariables,
TypeFamilies, TypeOperators, GADTs, UndecidableInstances,
FlexibleContexts, DefaultSignatures, BangPatterns,
InstanceSigs #-}
module Data.Singletons.Prelude.Enum (
PBounded(..), SBounded(..),
PEnum(..), SEnum(..),
MinBoundSym0,
MaxBoundSym0,
SuccSym0, SuccSym1,
PredSym0, PredSym1,
ToEnumSym0, ToEnumSym1,
FromEnumSym0, FromEnumSym1,
EnumFromToSym0, EnumFromToSym1, EnumFromToSym2,
EnumFromThenToSym0, EnumFromThenToSym1, EnumFromThenToSym2,
EnumFromThenToSym3
) where
import Data.Singletons.Single
import Data.Singletons.Util
import Data.Singletons.Prelude.Num
import Data.Singletons.Prelude.Base
import Data.Singletons.Prelude.Ord
import Data.Singletons.Prelude.Eq
import Data.Singletons.Prelude.Instances
import Data.Singletons.TypeLits
$(singletonsOnly [d|
class Bounded a where
minBound, maxBound :: a
|])
$(singBoundedInstances boundedBasicTypes)
$(singletonsOnly [d|
class Enum a where
succ :: a -> a
pred :: a -> a
toEnum :: Nat -> a
fromEnum :: a -> Nat
enumFromTo :: a -> a -> [a]
enumFromThenTo :: a -> a -> a -> [a]
succ = toEnum . (+1) . fromEnum
pred = toEnum . (subtract 1) . fromEnum
enumFromTo x y = map toEnum [fromEnum x .. fromEnum y]
enumFromThenTo x1 x2 y = map toEnum [fromEnum x1, fromEnum x2 .. fromEnum y]
eftNat :: Nat -> Nat -> [Nat]
eftNat x0 y | (x0 > y) = []
| otherwise = go x0
where
go x = x : if (x == y) then [] else go (x + 1)
efdtNat :: Nat -> Nat -> Nat -> [Nat]
efdtNat x1 x2 y
| x2 >= x1 = efdtNatUp x1 x2 y
| otherwise = efdtNatDn x1 x2 y
efdtNatUp :: Nat -> Nat -> Nat -> [Nat]
efdtNatUp x1 x2 y
| y < x2 = if y < x1 then [] else [x1]
| otherwise =
let delta = x2 - x1
y' = y - delta
go_up x | x > y' = [x]
| otherwise = x : go_up (x + delta)
in x1 : go_up x2
efdtNatDn :: Nat -> Nat -> Nat -> [Nat]
efdtNatDn x1 x2 y
| y > x2 = if y > x1 then [] else [x1]
| otherwise =
let delta = x2 - x1
y' = y - delta
go_dn x | x < y' = [x]
| otherwise = x : go_dn (x + delta)
in x1 : go_dn x2
instance Enum Nat where
succ x = x + 1
pred x = x - 1
toEnum x = x
fromEnum x = x
enumFromTo = eftNat
enumFromThenTo = efdtNat
|])
$(singEnumInstances enumBasicTypes)