{- ORMOLU_DISABLE -}
-- Implicit CAD. Copyright (C) 2011, Christopher Olah (chris@colah.ca)
-- Copyright 2014-2019, Julia Longtin (julial@turinglace.com)
-- Released under the GNU AGPLV3+, see LICENSE

-- Lift the numeric instances where we can
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- Suppress a warning about the derived Integral instance
{-# OPTIONS_GHC -Wno-identities #-}

module Graphics.Implicit.IntegralUtil (, toℕ, fromℕ) where

import Prelude (Integral, Integer, Int, Show, Read, Eq, Ord, Num, Enum, Integral, Real, ($), fromIntegral, (.))

-- So we can produce an instance of Fastℕ for ℕ.
import Graphics.Implicit.FastIntUtil (Fastℕ(Fastℕ))

-- the N typeclass. only used to define the ℕ type.
class (Integral n) => N n where
  fromℕ ::  -> n
  toℕ :: n -> 

instance N Integer where
  fromℕ :: ℕ -> Integer
fromℕ ( Integer
a) = Integer
a
  {-# INLINABLE fromℕ #-}
  toℕ :: Integer -> ℕ
toℕ = Integer -> ℕ

  {-# INLINABLE toℕ #-}

instance N Fastℕ where
  fromℕ :: ℕ -> Fastℕ
fromℕ ( Integer
a) = Int -> Fastℕ
Fastℕ (Int -> Fastℕ) -> Int -> Fastℕ
forall a b. (a -> b) -> a -> b
$ Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a
  {-# INLINABLE fromℕ #-}
  toℕ :: Fastℕ -> ℕ
toℕ = Integer -> ℕ
 (Integer -> ℕ) -> (Fastℕ -> Integer) -> Fastℕ -> ℕ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fastℕ -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
  {-# INLINABLE toℕ #-}

instance N Int where
  fromℕ :: ℕ -> Int
fromℕ ( Integer
a) = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
a
  {-# INLINABLE fromℕ #-}
  toℕ :: Int -> ℕ
toℕ = Integer -> ℕ
 (Integer -> ℕ) -> (Int -> Integer) -> Int -> ℕ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
  {-# INLINABLE toℕ #-}

-- Arbitrary precision integers. To be used for anything countable, or in ratios.
-- When Read and Show instances exist on a given type they need to satisfy
-- read . show = id
newtype  =  Integer
 deriving (Int -> ℕ -> ShowS
[ℕ] -> ShowS
ℕ -> String
(Int -> ℕ -> ShowS) -> (ℕ -> String) -> ([ℕ] -> ShowS) -> Show ℕ
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ℕ] -> ShowS
$cshowList :: [ℕ] -> ShowS
show :: ℕ -> String
$cshow :: ℕ -> String
showsPrec :: Int -> ℕ -> ShowS
$cshowsPrec :: Int -> ℕ -> ShowS
Show, ReadPrec [ℕ]
ReadPrec ℕ
Int -> ReadS ℕ
ReadS [ℕ]
(Int -> ReadS ℕ)
-> ReadS [ℕ] -> ReadPrec ℕ -> ReadPrec [ℕ] -> Read ℕ
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ℕ]
$creadListPrec :: ReadPrec [ℕ]
readPrec :: ReadPrec ℕ
$creadPrec :: ReadPrec ℕ
readList :: ReadS [ℕ]
$creadList :: ReadS [ℕ]
readsPrec :: Int -> ReadS ℕ
$creadsPrec :: Int -> ReadS ℕ
Read, ℕ -> ℕ -> Bool
(ℕ -> ℕ -> Bool) -> (ℕ -> ℕ -> Bool) -> Eq ℕ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ℕ -> ℕ -> Bool
$c/= :: ℕ -> ℕ -> Bool
== :: ℕ -> ℕ -> Bool
$c== :: ℕ -> ℕ -> Bool
Eq, Eq ℕ
Eq ℕ
-> (ℕ -> ℕ -> Ordering)
-> (ℕ -> ℕ -> Bool)
-> (ℕ -> ℕ -> Bool)
-> (ℕ -> ℕ -> Bool)
-> (ℕ -> ℕ -> Bool)
-> (ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ -> ℕ)
-> Ord ℕ
ℕ -> ℕ -> Bool
ℕ -> ℕ -> Ordering
ℕ -> ℕ -> ℕ
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ℕ -> ℕ -> ℕ
$cmin :: ℕ -> ℕ -> ℕ
max :: ℕ -> ℕ -> ℕ
$cmax :: ℕ -> ℕ -> ℕ
>= :: ℕ -> ℕ -> Bool
$c>= :: ℕ -> ℕ -> Bool
> :: ℕ -> ℕ -> Bool
$c> :: ℕ -> ℕ -> Bool
<= :: ℕ -> ℕ -> Bool
$c<= :: ℕ -> ℕ -> Bool
< :: ℕ -> ℕ -> Bool
$c< :: ℕ -> ℕ -> Bool
compare :: ℕ -> ℕ -> Ordering
$ccompare :: ℕ -> ℕ -> Ordering
$cp1Ord :: Eq ℕ
Ord, Integer -> ℕ
ℕ -> ℕ
ℕ -> ℕ -> ℕ
(ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ)
-> (ℕ -> ℕ)
-> (ℕ -> ℕ)
-> (Integer -> ℕ)
-> Num ℕ
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ℕ
$cfromInteger :: Integer -> ℕ
signum :: ℕ -> ℕ
$csignum :: ℕ -> ℕ
abs :: ℕ -> ℕ
$cabs :: ℕ -> ℕ
negate :: ℕ -> ℕ
$cnegate :: ℕ -> ℕ
* :: ℕ -> ℕ -> ℕ
$c* :: ℕ -> ℕ -> ℕ
- :: ℕ -> ℕ -> ℕ
$c- :: ℕ -> ℕ -> ℕ
+ :: ℕ -> ℕ -> ℕ
$c+ :: ℕ -> ℕ -> ℕ
Num, Int -> ℕ
ℕ -> Int
ℕ -> [ℕ]
ℕ -> ℕ
ℕ -> ℕ -> [ℕ]
ℕ -> ℕ -> ℕ -> [ℕ]
(ℕ -> ℕ)
-> (ℕ -> ℕ)
-> (Int -> ℕ)
-> (ℕ -> Int)
-> (ℕ -> [ℕ])
-> (ℕ -> ℕ -> [ℕ])
-> (ℕ -> ℕ -> [ℕ])
-> (ℕ -> ℕ -> ℕ -> [ℕ])
-> Enum ℕ
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ℕ -> ℕ -> ℕ -> [ℕ]
$cenumFromThenTo :: ℕ -> ℕ -> ℕ -> [ℕ]
enumFromTo :: ℕ -> ℕ -> [ℕ]
$cenumFromTo :: ℕ -> ℕ -> [ℕ]
enumFromThen :: ℕ -> ℕ -> [ℕ]
$cenumFromThen :: ℕ -> ℕ -> [ℕ]
enumFrom :: ℕ -> [ℕ]
$cenumFrom :: ℕ -> [ℕ]
fromEnum :: ℕ -> Int
$cfromEnum :: ℕ -> Int
toEnum :: Int -> ℕ
$ctoEnum :: Int -> ℕ
pred :: ℕ -> ℕ
$cpred :: ℕ -> ℕ
succ :: ℕ -> ℕ
$csucc :: ℕ -> ℕ
Enum, Enum ℕ
Real ℕ
Real ℕ
-> Enum ℕ
-> (ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ -> ℕ)
-> (ℕ -> ℕ -> (ℕ, ℕ))
-> (ℕ -> ℕ -> (ℕ, ℕ))
-> (ℕ -> Integer)
-> Integral ℕ
ℕ -> Integer
ℕ -> ℕ -> (ℕ, ℕ)
ℕ -> ℕ -> ℕ
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ℕ -> Integer
$ctoInteger :: ℕ -> Integer
divMod :: ℕ -> ℕ -> (ℕ, ℕ)
$cdivMod :: ℕ -> ℕ -> (ℕ, ℕ)
quotRem :: ℕ -> ℕ -> (ℕ, ℕ)
$cquotRem :: ℕ -> ℕ -> (ℕ, ℕ)
mod :: ℕ -> ℕ -> ℕ
$cmod :: ℕ -> ℕ -> ℕ
div :: ℕ -> ℕ -> ℕ
$cdiv :: ℕ -> ℕ -> ℕ
rem :: ℕ -> ℕ -> ℕ
$crem :: ℕ -> ℕ -> ℕ
quot :: ℕ -> ℕ -> ℕ
$cquot :: ℕ -> ℕ -> ℕ
$cp2Integral :: Enum ℕ
$cp1Integral :: Real ℕ
Integral, Num ℕ
Ord ℕ
Num ℕ -> Ord ℕ -> (ℕ -> Rational) -> Real ℕ
ℕ -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ℕ -> Rational
$ctoRational :: ℕ -> Rational
$cp2Real :: Ord ℕ
$cp1Real :: Num ℕ
Real)