{-# LANGUAGE DeriveAnyClass    #-}
{-# LANGUAGE NoImplicitPrelude #-}

{-|
Module      : Headroom.FileType.Types
Description : Data types for "Headroom.FileType"
Copyright   : (c) 2019-2020 Vaclav Svejcar
License     : BSD-3-Clause
Maintainer  : vaclav.svejcar@gmail.com
Stability   : experimental
Portability : POSIX

This module contains data types for "Headroom.FileType" modules.
-}

module Headroom.FileType.Types where

import           Headroom.Data.EnumExtra        ( EnumExtra(..) )
import           RIO

-- | Supported type of source code file.
data FileType
  = C
  -- ^ support for /C/ programming language
  | CPP
  -- ^ support for /C++/ programming language
  | CSS
  -- ^ support for /CSS/
  | Haskell
  -- ^ support for /Haskell/ programming language
  | HTML
  -- ^ support for /HTML/
  | Java
  -- ^ support for /Java/ programming language
  | JS
  -- ^ support for /JavaScript/ programming language
  | PureScript
  -- ^ support for /PureScript/ programming language
  | Rust
  -- ^ support for /Rust/ programming language
  | Scala
  -- ^ support for /Scala/ programming language
  | Shell
  -- ^ support for /Shell/
  deriving (FileType
FileType -> FileType -> Bounded FileType
forall a. a -> a -> Bounded a
maxBound :: FileType
$cmaxBound :: FileType
minBound :: FileType
$cminBound :: FileType
Bounded, Int -> FileType
FileType -> Int
FileType -> [FileType]
FileType -> FileType
FileType -> FileType -> [FileType]
FileType -> FileType -> FileType -> [FileType]
(FileType -> FileType)
-> (FileType -> FileType)
-> (Int -> FileType)
-> (FileType -> Int)
-> (FileType -> [FileType])
-> (FileType -> FileType -> [FileType])
-> (FileType -> FileType -> [FileType])
-> (FileType -> FileType -> FileType -> [FileType])
-> Enum FileType
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 :: FileType -> FileType -> FileType -> [FileType]
$cenumFromThenTo :: FileType -> FileType -> FileType -> [FileType]
enumFromTo :: FileType -> FileType -> [FileType]
$cenumFromTo :: FileType -> FileType -> [FileType]
enumFromThen :: FileType -> FileType -> [FileType]
$cenumFromThen :: FileType -> FileType -> [FileType]
enumFrom :: FileType -> [FileType]
$cenumFrom :: FileType -> [FileType]
fromEnum :: FileType -> Int
$cfromEnum :: FileType -> Int
toEnum :: Int -> FileType
$ctoEnum :: Int -> FileType
pred :: FileType -> FileType
$cpred :: FileType -> FileType
succ :: FileType -> FileType
$csucc :: FileType -> FileType
Enum, Bounded FileType
Enum FileType
Eq FileType
Ord FileType
Show FileType
[FileType]
Text
Bounded FileType
-> Enum FileType
-> Eq FileType
-> Ord FileType
-> Show FileType
-> [FileType]
-> Text
-> (FileType -> Text)
-> (Text -> Maybe FileType)
-> EnumExtra FileType
Text -> Maybe FileType
FileType -> Text
forall a.
Bounded a
-> Enum a
-> Eq a
-> Ord a
-> Show a
-> [a]
-> Text
-> (a -> Text)
-> (Text -> Maybe a)
-> EnumExtra a
textToEnum :: Text -> Maybe FileType
$ctextToEnum :: Text -> Maybe FileType
enumToText :: FileType -> Text
$cenumToText :: FileType -> Text
allValuesToText :: Text
$callValuesToText :: Text
allValues :: [FileType]
$callValues :: [FileType]
$cp5EnumExtra :: Show FileType
$cp4EnumExtra :: Ord FileType
$cp3EnumExtra :: Eq FileType
$cp2EnumExtra :: Enum FileType
$cp1EnumExtra :: Bounded FileType
EnumExtra, FileType -> FileType -> Bool
(FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool) -> Eq FileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileType -> FileType -> Bool
$c/= :: FileType -> FileType -> Bool
== :: FileType -> FileType -> Bool
$c== :: FileType -> FileType -> Bool
Eq, Eq FileType
Eq FileType
-> (FileType -> FileType -> Ordering)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool)
-> (FileType -> FileType -> FileType)
-> (FileType -> FileType -> FileType)
-> Ord FileType
FileType -> FileType -> Bool
FileType -> FileType -> Ordering
FileType -> FileType -> FileType
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 :: FileType -> FileType -> FileType
$cmin :: FileType -> FileType -> FileType
max :: FileType -> FileType -> FileType
$cmax :: FileType -> FileType -> FileType
>= :: FileType -> FileType -> Bool
$c>= :: FileType -> FileType -> Bool
> :: FileType -> FileType -> Bool
$c> :: FileType -> FileType -> Bool
<= :: FileType -> FileType -> Bool
$c<= :: FileType -> FileType -> Bool
< :: FileType -> FileType -> Bool
$c< :: FileType -> FileType -> Bool
compare :: FileType -> FileType -> Ordering
$ccompare :: FileType -> FileType -> Ordering
$cp1Ord :: Eq FileType
Ord, Int -> FileType -> ShowS
[FileType] -> ShowS
FileType -> String
(Int -> FileType -> ShowS)
-> (FileType -> String) -> ([FileType] -> ShowS) -> Show FileType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileType] -> ShowS
$cshowList :: [FileType] -> ShowS
show :: FileType -> String
$cshow :: FileType -> String
showsPrec :: Int -> FileType -> ShowS
$cshowsPrec :: Int -> FileType -> ShowS
Show)