{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} module Continent.Unsafe ( Continent (..) , pattern Africa , pattern Asia , pattern Antarctica , pattern Europe , pattern NorthAmerica , pattern Oceania , pattern SouthAmerica , continentNameDb ) where import Data.Text (Text) import Data.Word (Word8) newtype Continent = Continent Word8 deriving (Continent -> Continent -> Bool (Continent -> Continent -> Bool) -> (Continent -> Continent -> Bool) -> Eq Continent forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Continent -> Continent -> Bool == :: Continent -> Continent -> Bool $c/= :: Continent -> Continent -> Bool /= :: Continent -> Continent -> Bool Eq, Eq Continent Eq Continent => (Continent -> Continent -> Ordering) -> (Continent -> Continent -> Bool) -> (Continent -> Continent -> Bool) -> (Continent -> Continent -> Bool) -> (Continent -> Continent -> Bool) -> (Continent -> Continent -> Continent) -> (Continent -> Continent -> Continent) -> Ord Continent Continent -> Continent -> Bool Continent -> Continent -> Ordering Continent -> Continent -> Continent 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 $ccompare :: Continent -> Continent -> Ordering compare :: Continent -> Continent -> Ordering $c< :: Continent -> Continent -> Bool < :: Continent -> Continent -> Bool $c<= :: Continent -> Continent -> Bool <= :: Continent -> Continent -> Bool $c> :: Continent -> Continent -> Bool > :: Continent -> Continent -> Bool $c>= :: Continent -> Continent -> Bool >= :: Continent -> Continent -> Bool $cmax :: Continent -> Continent -> Continent max :: Continent -> Continent -> Continent $cmin :: Continent -> Continent -> Continent min :: Continent -> Continent -> Continent Ord, Int -> Continent Continent -> Int Continent -> [Continent] Continent -> Continent Continent -> Continent -> [Continent] Continent -> Continent -> Continent -> [Continent] (Continent -> Continent) -> (Continent -> Continent) -> (Int -> Continent) -> (Continent -> Int) -> (Continent -> [Continent]) -> (Continent -> Continent -> [Continent]) -> (Continent -> Continent -> [Continent]) -> (Continent -> Continent -> Continent -> [Continent]) -> Enum Continent forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a $csucc :: Continent -> Continent succ :: Continent -> Continent $cpred :: Continent -> Continent pred :: Continent -> Continent $ctoEnum :: Int -> Continent toEnum :: Int -> Continent $cfromEnum :: Continent -> Int fromEnum :: Continent -> Int $cenumFrom :: Continent -> [Continent] enumFrom :: Continent -> [Continent] $cenumFromThen :: Continent -> Continent -> [Continent] enumFromThen :: Continent -> Continent -> [Continent] $cenumFromTo :: Continent -> Continent -> [Continent] enumFromTo :: Continent -> Continent -> [Continent] $cenumFromThenTo :: Continent -> Continent -> Continent -> [Continent] enumFromThenTo :: Continent -> Continent -> Continent -> [Continent] Enum) {-# COMPLETE Africa, Asia, Antarctica, Europe, NorthAmerica, Oceania, SouthAmerica #-} pattern Africa, Asia, Antarctica, Europe, NorthAmerica, Oceania, SouthAmerica :: Continent pattern $mAfrica :: forall {r}. Continent -> ((# #) -> r) -> ((# #) -> r) -> r $bAfrica :: Continent Africa = Continent 0 pattern $mAsia :: forall {r}. Continent -> ((# #) -> r) -> ((# #) -> r) -> r $bAsia :: Continent Asia = Continent 1 pattern $mAntarctica :: forall {r}. Continent -> ((# #) -> r) -> ((# #) -> r) -> r $bAntarctica :: Continent Antarctica = Continent 2 pattern $mEurope :: forall {r}. Continent -> ((# #) -> r) -> ((# #) -> r) -> r $bEurope :: Continent Europe = Continent 3 pattern $mNorthAmerica :: forall {r}. Continent -> ((# #) -> r) -> ((# #) -> r) -> r $bNorthAmerica :: Continent NorthAmerica = Continent 4 pattern $mOceania :: forall {r}. Continent -> ((# #) -> r) -> ((# #) -> r) -> r $bOceania :: Continent Oceania = Continent 5 pattern $mSouthAmerica :: forall {r}. Continent -> ((# #) -> r) -> ((# #) -> r) -> r $bSouthAmerica :: Continent SouthAmerica = Continent 6 continentNameDb :: [(Word8, Text, (Char, Char))] continentNameDb :: [(Word8, Text, (Char, Char))] continentNameDb = [ (Word8 0, Text "Africa", (Char 'A', Char 'F')) , (Word8 1, Text "Asia", (Char 'A', Char 'N')) , (Word8 2, Text "Antarctica", (Char 'A', Char 'S')) , (Word8 3, Text "Europe", (Char 'E', Char 'U')) , (Word8 4, Text "North america", (Char 'N', Char 'A')) , (Word8 5, Text "Oceania", (Char 'O', Char 'C')) , (Word8 6, Text "South america", (Char 'S', Char 'A')) ] instance Bounded Continent where minBound :: Continent minBound = Word8 -> Continent Continent Word8 0 maxBound :: Continent maxBound = Word8 -> Continent Continent Word8 6 instance Show Continent where show :: Continent -> String show Continent Africa = String "Africa" show Continent Asia = String "Asia" show Continent Antarctica = String "Antarctica" show Continent Europe = String "Europe" show Continent NorthAmerica = String "NorthAmerica" show Continent Oceania = String "Oceania" show Continent SouthAmerica = String "SouthAmerica"