{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Poseidon.ColumnTypesSSF where
import Poseidon.AccessionIDs
import Poseidon.ColumnTypesUtils
import Data.Char (isHexDigit)
import qualified Data.Csv as Csv
import qualified Data.Text as T
import qualified Data.Text.Read as T
import Data.Time (Day)
import Data.Time.Format (defaultTimeLocale, formatTime,
parseTimeM)
import GHC.Generics (Generic)
import Network.URI (isURIReference)
data SSFUDG =
SSFMinus
| SSFHalf
| SSFPlus
deriving (SSFUDG -> SSFUDG -> Bool
(SSFUDG -> SSFUDG -> Bool)
-> (SSFUDG -> SSFUDG -> Bool) -> Eq SSFUDG
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFUDG -> SSFUDG -> Bool
== :: SSFUDG -> SSFUDG -> Bool
$c/= :: SSFUDG -> SSFUDG -> Bool
/= :: SSFUDG -> SSFUDG -> Bool
Eq, Eq SSFUDG
Eq SSFUDG =>
(SSFUDG -> SSFUDG -> Ordering)
-> (SSFUDG -> SSFUDG -> Bool)
-> (SSFUDG -> SSFUDG -> Bool)
-> (SSFUDG -> SSFUDG -> Bool)
-> (SSFUDG -> SSFUDG -> Bool)
-> (SSFUDG -> SSFUDG -> SSFUDG)
-> (SSFUDG -> SSFUDG -> SSFUDG)
-> Ord SSFUDG
SSFUDG -> SSFUDG -> Bool
SSFUDG -> SSFUDG -> Ordering
SSFUDG -> SSFUDG -> SSFUDG
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 :: SSFUDG -> SSFUDG -> Ordering
compare :: SSFUDG -> SSFUDG -> Ordering
$c< :: SSFUDG -> SSFUDG -> Bool
< :: SSFUDG -> SSFUDG -> Bool
$c<= :: SSFUDG -> SSFUDG -> Bool
<= :: SSFUDG -> SSFUDG -> Bool
$c> :: SSFUDG -> SSFUDG -> Bool
> :: SSFUDG -> SSFUDG -> Bool
$c>= :: SSFUDG -> SSFUDG -> Bool
>= :: SSFUDG -> SSFUDG -> Bool
$cmax :: SSFUDG -> SSFUDG -> SSFUDG
max :: SSFUDG -> SSFUDG -> SSFUDG
$cmin :: SSFUDG -> SSFUDG -> SSFUDG
min :: SSFUDG -> SSFUDG -> SSFUDG
Ord, (forall x. SSFUDG -> Rep SSFUDG x)
-> (forall x. Rep SSFUDG x -> SSFUDG) -> Generic SSFUDG
forall x. Rep SSFUDG x -> SSFUDG
forall x. SSFUDG -> Rep SSFUDG x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFUDG -> Rep SSFUDG x
from :: forall x. SSFUDG -> Rep SSFUDG x
$cto :: forall x. Rep SSFUDG x -> SSFUDG
to :: forall x. Rep SSFUDG x -> SSFUDG
Generic, Int -> SSFUDG
SSFUDG -> Int
SSFUDG -> [SSFUDG]
SSFUDG -> SSFUDG
SSFUDG -> SSFUDG -> [SSFUDG]
SSFUDG -> SSFUDG -> SSFUDG -> [SSFUDG]
(SSFUDG -> SSFUDG)
-> (SSFUDG -> SSFUDG)
-> (Int -> SSFUDG)
-> (SSFUDG -> Int)
-> (SSFUDG -> [SSFUDG])
-> (SSFUDG -> SSFUDG -> [SSFUDG])
-> (SSFUDG -> SSFUDG -> [SSFUDG])
-> (SSFUDG -> SSFUDG -> SSFUDG -> [SSFUDG])
-> Enum SSFUDG
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 :: SSFUDG -> SSFUDG
succ :: SSFUDG -> SSFUDG
$cpred :: SSFUDG -> SSFUDG
pred :: SSFUDG -> SSFUDG
$ctoEnum :: Int -> SSFUDG
toEnum :: Int -> SSFUDG
$cfromEnum :: SSFUDG -> Int
fromEnum :: SSFUDG -> Int
$cenumFrom :: SSFUDG -> [SSFUDG]
enumFrom :: SSFUDG -> [SSFUDG]
$cenumFromThen :: SSFUDG -> SSFUDG -> [SSFUDG]
enumFromThen :: SSFUDG -> SSFUDG -> [SSFUDG]
$cenumFromTo :: SSFUDG -> SSFUDG -> [SSFUDG]
enumFromTo :: SSFUDG -> SSFUDG -> [SSFUDG]
$cenumFromThenTo :: SSFUDG -> SSFUDG -> SSFUDG -> [SSFUDG]
enumFromThenTo :: SSFUDG -> SSFUDG -> SSFUDG -> [SSFUDG]
Enum, SSFUDG
SSFUDG -> SSFUDG -> Bounded SSFUDG
forall a. a -> a -> Bounded a
$cminBound :: SSFUDG
minBound :: SSFUDG
$cmaxBound :: SSFUDG
maxBound :: SSFUDG
Bounded)
instance Makeable SSFUDG where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFUDG
make Text
x
| Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"minus" = SSFUDG -> m SSFUDG
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SSFUDG
SSFMinus
| Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"half" = SSFUDG -> m SSFUDG
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SSFUDG
SSFHalf
| Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"plus" = SSFUDG -> m SSFUDG
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SSFUDG
SSFPlus
| Bool
otherwise = [Char] -> m SSFUDG
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFUDG) -> [Char] -> m SSFUDG
forall a b. (a -> b) -> a -> b
$ [Char]
"udg is set to " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
"That is not in the allowed set [minus, half, plus]."
instance Suspicious SSFUDG where inspect :: SSFUDG -> Maybe [[Char]]
inspect SSFUDG
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFUDG where
show :: SSFUDG -> [Char]
show SSFUDG
SSFMinus = [Char]
"minus"
show SSFUDG
SSFHalf = [Char]
"half"
show SSFUDG
SSFPlus = [Char]
"plus"
instance Csv.ToField SSFUDG where toField :: SSFUDG -> Field
toField SSFUDG
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFUDG -> [Char]
forall a. Show a => a -> [Char]
show SSFUDG
x
instance Csv.FromField SSFUDG where parseField :: Field -> Parser SSFUDG
parseField = [Char] -> Field -> Parser SSFUDG
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"udg"
data SSFLibraryBuilt =
SSFDS
| SSFSS
deriving (SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
(SSFLibraryBuilt -> SSFLibraryBuilt -> Bool)
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> Bool)
-> Eq SSFLibraryBuilt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
== :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
$c/= :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
/= :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
Eq, Eq SSFLibraryBuilt
Eq SSFLibraryBuilt =>
(SSFLibraryBuilt -> SSFLibraryBuilt -> Ordering)
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> Bool)
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> Bool)
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> Bool)
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> Bool)
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> SSFLibraryBuilt)
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> SSFLibraryBuilt)
-> Ord SSFLibraryBuilt
SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
SSFLibraryBuilt -> SSFLibraryBuilt -> Ordering
SSFLibraryBuilt -> SSFLibraryBuilt -> SSFLibraryBuilt
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 :: SSFLibraryBuilt -> SSFLibraryBuilt -> Ordering
compare :: SSFLibraryBuilt -> SSFLibraryBuilt -> Ordering
$c< :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
< :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
$c<= :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
<= :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
$c> :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
> :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
$c>= :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
>= :: SSFLibraryBuilt -> SSFLibraryBuilt -> Bool
$cmax :: SSFLibraryBuilt -> SSFLibraryBuilt -> SSFLibraryBuilt
max :: SSFLibraryBuilt -> SSFLibraryBuilt -> SSFLibraryBuilt
$cmin :: SSFLibraryBuilt -> SSFLibraryBuilt -> SSFLibraryBuilt
min :: SSFLibraryBuilt -> SSFLibraryBuilt -> SSFLibraryBuilt
Ord, (forall x. SSFLibraryBuilt -> Rep SSFLibraryBuilt x)
-> (forall x. Rep SSFLibraryBuilt x -> SSFLibraryBuilt)
-> Generic SSFLibraryBuilt
forall x. Rep SSFLibraryBuilt x -> SSFLibraryBuilt
forall x. SSFLibraryBuilt -> Rep SSFLibraryBuilt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFLibraryBuilt -> Rep SSFLibraryBuilt x
from :: forall x. SSFLibraryBuilt -> Rep SSFLibraryBuilt x
$cto :: forall x. Rep SSFLibraryBuilt x -> SSFLibraryBuilt
to :: forall x. Rep SSFLibraryBuilt x -> SSFLibraryBuilt
Generic, Int -> SSFLibraryBuilt
SSFLibraryBuilt -> Int
SSFLibraryBuilt -> [SSFLibraryBuilt]
SSFLibraryBuilt -> SSFLibraryBuilt
SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
SSFLibraryBuilt
-> SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
(SSFLibraryBuilt -> SSFLibraryBuilt)
-> (SSFLibraryBuilt -> SSFLibraryBuilt)
-> (Int -> SSFLibraryBuilt)
-> (SSFLibraryBuilt -> Int)
-> (SSFLibraryBuilt -> [SSFLibraryBuilt])
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt])
-> (SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt])
-> (SSFLibraryBuilt
-> SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt])
-> Enum SSFLibraryBuilt
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 :: SSFLibraryBuilt -> SSFLibraryBuilt
succ :: SSFLibraryBuilt -> SSFLibraryBuilt
$cpred :: SSFLibraryBuilt -> SSFLibraryBuilt
pred :: SSFLibraryBuilt -> SSFLibraryBuilt
$ctoEnum :: Int -> SSFLibraryBuilt
toEnum :: Int -> SSFLibraryBuilt
$cfromEnum :: SSFLibraryBuilt -> Int
fromEnum :: SSFLibraryBuilt -> Int
$cenumFrom :: SSFLibraryBuilt -> [SSFLibraryBuilt]
enumFrom :: SSFLibraryBuilt -> [SSFLibraryBuilt]
$cenumFromThen :: SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
enumFromThen :: SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
$cenumFromTo :: SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
enumFromTo :: SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
$cenumFromThenTo :: SSFLibraryBuilt
-> SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
enumFromThenTo :: SSFLibraryBuilt
-> SSFLibraryBuilt -> SSFLibraryBuilt -> [SSFLibraryBuilt]
Enum, SSFLibraryBuilt
SSFLibraryBuilt -> SSFLibraryBuilt -> Bounded SSFLibraryBuilt
forall a. a -> a -> Bounded a
$cminBound :: SSFLibraryBuilt
minBound :: SSFLibraryBuilt
$cmaxBound :: SSFLibraryBuilt
maxBound :: SSFLibraryBuilt
Bounded)
instance Makeable SSFLibraryBuilt where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFLibraryBuilt
make Text
x
| Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"ds" = SSFLibraryBuilt -> m SSFLibraryBuilt
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SSFLibraryBuilt
SSFDS
| Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"ss" = SSFLibraryBuilt -> m SSFLibraryBuilt
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SSFLibraryBuilt
SSFSS
| Bool
otherwise = [Char] -> m SSFLibraryBuilt
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFLibraryBuilt) -> [Char] -> m SSFLibraryBuilt
forall a b. (a -> b) -> a -> b
$ [Char]
"library_built is set to " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
"That is not in [ds, ss]."
instance Suspicious SSFLibraryBuilt where inspect :: SSFLibraryBuilt -> Maybe [[Char]]
inspect SSFLibraryBuilt
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFLibraryBuilt where
show :: SSFLibraryBuilt -> [Char]
show SSFLibraryBuilt
SSFDS = [Char]
"ds"
show SSFLibraryBuilt
SSFSS = [Char]
"ss"
instance Csv.ToField SSFLibraryBuilt where toField :: SSFLibraryBuilt -> Field
toField SSFLibraryBuilt
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFLibraryBuilt -> [Char]
forall a. Show a => a -> [Char]
show SSFLibraryBuilt
x
instance Csv.FromField SSFLibraryBuilt where parseField :: Field -> Parser SSFLibraryBuilt
parseField = [Char] -> Field -> Parser SSFLibraryBuilt
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"library_built"
newtype SSFAccessionIDSample = SSFAccessionIDSample AccessionID
deriving (SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
(SSFAccessionIDSample -> SSFAccessionIDSample -> Bool)
-> (SSFAccessionIDSample -> SSFAccessionIDSample -> Bool)
-> Eq SSFAccessionIDSample
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
== :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
$c/= :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
/= :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
Eq, Eq SSFAccessionIDSample
Eq SSFAccessionIDSample =>
(SSFAccessionIDSample -> SSFAccessionIDSample -> Ordering)
-> (SSFAccessionIDSample -> SSFAccessionIDSample -> Bool)
-> (SSFAccessionIDSample -> SSFAccessionIDSample -> Bool)
-> (SSFAccessionIDSample -> SSFAccessionIDSample -> Bool)
-> (SSFAccessionIDSample -> SSFAccessionIDSample -> Bool)
-> (SSFAccessionIDSample
-> SSFAccessionIDSample -> SSFAccessionIDSample)
-> (SSFAccessionIDSample
-> SSFAccessionIDSample -> SSFAccessionIDSample)
-> Ord SSFAccessionIDSample
SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
SSFAccessionIDSample -> SSFAccessionIDSample -> Ordering
SSFAccessionIDSample
-> SSFAccessionIDSample -> SSFAccessionIDSample
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 :: SSFAccessionIDSample -> SSFAccessionIDSample -> Ordering
compare :: SSFAccessionIDSample -> SSFAccessionIDSample -> Ordering
$c< :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
< :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
$c<= :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
<= :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
$c> :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
> :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
$c>= :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
>= :: SSFAccessionIDSample -> SSFAccessionIDSample -> Bool
$cmax :: SSFAccessionIDSample
-> SSFAccessionIDSample -> SSFAccessionIDSample
max :: SSFAccessionIDSample
-> SSFAccessionIDSample -> SSFAccessionIDSample
$cmin :: SSFAccessionIDSample
-> SSFAccessionIDSample -> SSFAccessionIDSample
min :: SSFAccessionIDSample
-> SSFAccessionIDSample -> SSFAccessionIDSample
Ord, (forall x. SSFAccessionIDSample -> Rep SSFAccessionIDSample x)
-> (forall x. Rep SSFAccessionIDSample x -> SSFAccessionIDSample)
-> Generic SSFAccessionIDSample
forall x. Rep SSFAccessionIDSample x -> SSFAccessionIDSample
forall x. SSFAccessionIDSample -> Rep SSFAccessionIDSample x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFAccessionIDSample -> Rep SSFAccessionIDSample x
from :: forall x. SSFAccessionIDSample -> Rep SSFAccessionIDSample x
$cto :: forall x. Rep SSFAccessionIDSample x -> SSFAccessionIDSample
to :: forall x. Rep SSFAccessionIDSample x -> SSFAccessionIDSample
Generic)
instance Makeable SSFAccessionIDSample where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFAccessionIDSample
make Text
x = do
AccessionID
accID <- Text -> m AccessionID
forall (m :: * -> *). MonadFail m => Text -> m AccessionID
makeAccessionID Text
x
SSFAccessionIDSample -> m SSFAccessionIDSample
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (SSFAccessionIDSample -> m SSFAccessionIDSample)
-> SSFAccessionIDSample -> m SSFAccessionIDSample
forall a b. (a -> b) -> a -> b
$ AccessionID -> SSFAccessionIDSample
SSFAccessionIDSample AccessionID
accID
instance Suspicious SSFAccessionIDSample where
inspect :: SSFAccessionIDSample -> Maybe [[Char]]
inspect (SSFAccessionIDSample AccessionID
x) =
case AccessionID
x of
(INSDCBioSample Text
_) -> Maybe [[Char]]
forall a. Maybe a
Nothing
(INSDCSample Text
_) -> Maybe [[Char]]
forall a. Maybe a
Nothing
AccessionID
i -> [[Char]] -> Maybe [[Char]]
forall a. a -> Maybe a
Just [[Char]
"sample_accession " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ AccessionID -> [Char]
forall a. Show a => a -> [Char]
show AccessionID
i [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a correct INSDC \
\biosample/sample accession."]
instance Show SSFAccessionIDSample where
show :: SSFAccessionIDSample -> [Char]
show (SSFAccessionIDSample AccessionID
x) = AccessionID -> [Char]
forall a. Show a => a -> [Char]
show AccessionID
x
instance Csv.ToField SSFAccessionIDSample where toField :: SSFAccessionIDSample -> Field
toField SSFAccessionIDSample
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFAccessionIDSample -> [Char]
forall a. Show a => a -> [Char]
show SSFAccessionIDSample
x
instance Csv.FromField SSFAccessionIDSample where parseField :: Field -> Parser SSFAccessionIDSample
parseField = [Char] -> Field -> Parser SSFAccessionIDSample
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"sample_accession"
newtype SSFAccessionIDStudy = SSFAccessionIDStudy AccessionID
deriving (SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
(SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool)
-> (SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool)
-> Eq SSFAccessionIDStudy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
== :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
$c/= :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
/= :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
Eq, Eq SSFAccessionIDStudy
Eq SSFAccessionIDStudy =>
(SSFAccessionIDStudy -> SSFAccessionIDStudy -> Ordering)
-> (SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool)
-> (SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool)
-> (SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool)
-> (SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool)
-> (SSFAccessionIDStudy
-> SSFAccessionIDStudy -> SSFAccessionIDStudy)
-> (SSFAccessionIDStudy
-> SSFAccessionIDStudy -> SSFAccessionIDStudy)
-> Ord SSFAccessionIDStudy
SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
SSFAccessionIDStudy -> SSFAccessionIDStudy -> Ordering
SSFAccessionIDStudy -> SSFAccessionIDStudy -> SSFAccessionIDStudy
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 :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Ordering
compare :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Ordering
$c< :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
< :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
$c<= :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
<= :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
$c> :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
> :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
$c>= :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
>= :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> Bool
$cmax :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> SSFAccessionIDStudy
max :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> SSFAccessionIDStudy
$cmin :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> SSFAccessionIDStudy
min :: SSFAccessionIDStudy -> SSFAccessionIDStudy -> SSFAccessionIDStudy
Ord, (forall x. SSFAccessionIDStudy -> Rep SSFAccessionIDStudy x)
-> (forall x. Rep SSFAccessionIDStudy x -> SSFAccessionIDStudy)
-> Generic SSFAccessionIDStudy
forall x. Rep SSFAccessionIDStudy x -> SSFAccessionIDStudy
forall x. SSFAccessionIDStudy -> Rep SSFAccessionIDStudy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFAccessionIDStudy -> Rep SSFAccessionIDStudy x
from :: forall x. SSFAccessionIDStudy -> Rep SSFAccessionIDStudy x
$cto :: forall x. Rep SSFAccessionIDStudy x -> SSFAccessionIDStudy
to :: forall x. Rep SSFAccessionIDStudy x -> SSFAccessionIDStudy
Generic)
instance Makeable SSFAccessionIDStudy where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFAccessionIDStudy
make Text
x = do
AccessionID
accID <- Text -> m AccessionID
forall (m :: * -> *). MonadFail m => Text -> m AccessionID
makeAccessionID Text
x
SSFAccessionIDStudy -> m SSFAccessionIDStudy
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (SSFAccessionIDStudy -> m SSFAccessionIDStudy)
-> SSFAccessionIDStudy -> m SSFAccessionIDStudy
forall a b. (a -> b) -> a -> b
$ AccessionID -> SSFAccessionIDStudy
SSFAccessionIDStudy AccessionID
accID
instance Suspicious SSFAccessionIDStudy where
inspect :: SSFAccessionIDStudy -> Maybe [[Char]]
inspect (SSFAccessionIDStudy AccessionID
x) =
case AccessionID
x of
(INSDCProject Text
_) -> Maybe [[Char]]
forall a. Maybe a
Nothing
(INSDCStudy Text
_) -> Maybe [[Char]]
forall a. Maybe a
Nothing
AccessionID
i -> [[Char]] -> Maybe [[Char]]
forall a. a -> Maybe a
Just [[Char]
"study_accession " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ AccessionID -> [Char]
forall a. Show a => a -> [Char]
show AccessionID
i [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a correct INSDC \
\project/study accession."]
instance Show SSFAccessionIDStudy where
show :: SSFAccessionIDStudy -> [Char]
show (SSFAccessionIDStudy AccessionID
x) = AccessionID -> [Char]
forall a. Show a => a -> [Char]
show AccessionID
x
instance Csv.ToField SSFAccessionIDStudy where toField :: SSFAccessionIDStudy -> Field
toField SSFAccessionIDStudy
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFAccessionIDStudy -> [Char]
forall a. Show a => a -> [Char]
show SSFAccessionIDStudy
x
instance Csv.FromField SSFAccessionIDStudy where parseField :: Field -> Parser SSFAccessionIDStudy
parseField = [Char] -> Field -> Parser SSFAccessionIDStudy
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"study_accession"
newtype SSFAccessionIDRun = SSFAccessionIDRun AccessionID
deriving (SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
(SSFAccessionIDRun -> SSFAccessionIDRun -> Bool)
-> (SSFAccessionIDRun -> SSFAccessionIDRun -> Bool)
-> Eq SSFAccessionIDRun
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
== :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
$c/= :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
/= :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
Eq, Eq SSFAccessionIDRun
Eq SSFAccessionIDRun =>
(SSFAccessionIDRun -> SSFAccessionIDRun -> Ordering)
-> (SSFAccessionIDRun -> SSFAccessionIDRun -> Bool)
-> (SSFAccessionIDRun -> SSFAccessionIDRun -> Bool)
-> (SSFAccessionIDRun -> SSFAccessionIDRun -> Bool)
-> (SSFAccessionIDRun -> SSFAccessionIDRun -> Bool)
-> (SSFAccessionIDRun -> SSFAccessionIDRun -> SSFAccessionIDRun)
-> (SSFAccessionIDRun -> SSFAccessionIDRun -> SSFAccessionIDRun)
-> Ord SSFAccessionIDRun
SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
SSFAccessionIDRun -> SSFAccessionIDRun -> Ordering
SSFAccessionIDRun -> SSFAccessionIDRun -> SSFAccessionIDRun
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 :: SSFAccessionIDRun -> SSFAccessionIDRun -> Ordering
compare :: SSFAccessionIDRun -> SSFAccessionIDRun -> Ordering
$c< :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
< :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
$c<= :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
<= :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
$c> :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
> :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
$c>= :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
>= :: SSFAccessionIDRun -> SSFAccessionIDRun -> Bool
$cmax :: SSFAccessionIDRun -> SSFAccessionIDRun -> SSFAccessionIDRun
max :: SSFAccessionIDRun -> SSFAccessionIDRun -> SSFAccessionIDRun
$cmin :: SSFAccessionIDRun -> SSFAccessionIDRun -> SSFAccessionIDRun
min :: SSFAccessionIDRun -> SSFAccessionIDRun -> SSFAccessionIDRun
Ord, (forall x. SSFAccessionIDRun -> Rep SSFAccessionIDRun x)
-> (forall x. Rep SSFAccessionIDRun x -> SSFAccessionIDRun)
-> Generic SSFAccessionIDRun
forall x. Rep SSFAccessionIDRun x -> SSFAccessionIDRun
forall x. SSFAccessionIDRun -> Rep SSFAccessionIDRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFAccessionIDRun -> Rep SSFAccessionIDRun x
from :: forall x. SSFAccessionIDRun -> Rep SSFAccessionIDRun x
$cto :: forall x. Rep SSFAccessionIDRun x -> SSFAccessionIDRun
to :: forall x. Rep SSFAccessionIDRun x -> SSFAccessionIDRun
Generic)
instance Makeable SSFAccessionIDRun where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFAccessionIDRun
make Text
x = do
AccessionID
accID <- Text -> m AccessionID
forall (m :: * -> *). MonadFail m => Text -> m AccessionID
makeAccessionID Text
x
SSFAccessionIDRun -> m SSFAccessionIDRun
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (SSFAccessionIDRun -> m SSFAccessionIDRun)
-> SSFAccessionIDRun -> m SSFAccessionIDRun
forall a b. (a -> b) -> a -> b
$ AccessionID -> SSFAccessionIDRun
SSFAccessionIDRun AccessionID
accID
instance Suspicious SSFAccessionIDRun where
inspect :: SSFAccessionIDRun -> Maybe [[Char]]
inspect (SSFAccessionIDRun AccessionID
x) =
case AccessionID
x of
(INSDCRun Text
_) -> Maybe [[Char]]
forall a. Maybe a
Nothing
AccessionID
i -> [[Char]] -> Maybe [[Char]]
forall a. a -> Maybe a
Just [[Char]
"run_accession " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ AccessionID -> [Char]
forall a. Show a => a -> [Char]
show AccessionID
i [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a correct INSDC \
\run accession."]
instance Show SSFAccessionIDRun where
show :: SSFAccessionIDRun -> [Char]
show (SSFAccessionIDRun AccessionID
x) = AccessionID -> [Char]
forall a. Show a => a -> [Char]
show AccessionID
x
instance Csv.ToField SSFAccessionIDRun where toField :: SSFAccessionIDRun -> Field
toField SSFAccessionIDRun
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFAccessionIDRun -> [Char]
forall a. Show a => a -> [Char]
show SSFAccessionIDRun
x
instance Csv.FromField SSFAccessionIDRun where parseField :: Field -> Parser SSFAccessionIDRun
parseField = [Char] -> Field -> Parser SSFAccessionIDRun
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"run_accession"
newtype SSFSampleAlias = SSFSampleAlias T.Text deriving (SSFSampleAlias -> SSFSampleAlias -> Bool
(SSFSampleAlias -> SSFSampleAlias -> Bool)
-> (SSFSampleAlias -> SSFSampleAlias -> Bool) -> Eq SSFSampleAlias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFSampleAlias -> SSFSampleAlias -> Bool
== :: SSFSampleAlias -> SSFSampleAlias -> Bool
$c/= :: SSFSampleAlias -> SSFSampleAlias -> Bool
/= :: SSFSampleAlias -> SSFSampleAlias -> Bool
Eq, Eq SSFSampleAlias
Eq SSFSampleAlias =>
(SSFSampleAlias -> SSFSampleAlias -> Ordering)
-> (SSFSampleAlias -> SSFSampleAlias -> Bool)
-> (SSFSampleAlias -> SSFSampleAlias -> Bool)
-> (SSFSampleAlias -> SSFSampleAlias -> Bool)
-> (SSFSampleAlias -> SSFSampleAlias -> Bool)
-> (SSFSampleAlias -> SSFSampleAlias -> SSFSampleAlias)
-> (SSFSampleAlias -> SSFSampleAlias -> SSFSampleAlias)
-> Ord SSFSampleAlias
SSFSampleAlias -> SSFSampleAlias -> Bool
SSFSampleAlias -> SSFSampleAlias -> Ordering
SSFSampleAlias -> SSFSampleAlias -> SSFSampleAlias
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 :: SSFSampleAlias -> SSFSampleAlias -> Ordering
compare :: SSFSampleAlias -> SSFSampleAlias -> Ordering
$c< :: SSFSampleAlias -> SSFSampleAlias -> Bool
< :: SSFSampleAlias -> SSFSampleAlias -> Bool
$c<= :: SSFSampleAlias -> SSFSampleAlias -> Bool
<= :: SSFSampleAlias -> SSFSampleAlias -> Bool
$c> :: SSFSampleAlias -> SSFSampleAlias -> Bool
> :: SSFSampleAlias -> SSFSampleAlias -> Bool
$c>= :: SSFSampleAlias -> SSFSampleAlias -> Bool
>= :: SSFSampleAlias -> SSFSampleAlias -> Bool
$cmax :: SSFSampleAlias -> SSFSampleAlias -> SSFSampleAlias
max :: SSFSampleAlias -> SSFSampleAlias -> SSFSampleAlias
$cmin :: SSFSampleAlias -> SSFSampleAlias -> SSFSampleAlias
min :: SSFSampleAlias -> SSFSampleAlias -> SSFSampleAlias
Ord)
$(makeInstances ''SSFSampleAlias "sample_alias")
newtype SSFSecondarySampleAccession = SSFSecondarySampleAccession T.Text deriving (SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
(SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Bool)
-> (SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Bool)
-> Eq SSFSecondarySampleAccession
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
== :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
$c/= :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
/= :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
Eq, Eq SSFSecondarySampleAccession
Eq SSFSecondarySampleAccession =>
(SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Ordering)
-> (SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Bool)
-> (SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Bool)
-> (SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Bool)
-> (SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Bool)
-> (SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> SSFSecondarySampleAccession)
-> (SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> SSFSecondarySampleAccession)
-> Ord SSFSecondarySampleAccession
SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Ordering
SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> SSFSecondarySampleAccession
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 :: SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Ordering
compare :: SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> Ordering
$c< :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
< :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
$c<= :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
<= :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
$c> :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
> :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
$c>= :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
>= :: SSFSecondarySampleAccession -> SSFSecondarySampleAccession -> Bool
$cmax :: SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> SSFSecondarySampleAccession
max :: SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> SSFSecondarySampleAccession
$cmin :: SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> SSFSecondarySampleAccession
min :: SSFSecondarySampleAccession
-> SSFSecondarySampleAccession -> SSFSecondarySampleAccession
Ord)
$(makeInstances ''SSFSecondarySampleAccession "secondary_sample_accession")
newtype SSFFirstPublicSimpleDate = SSFFirstPublicSimpleDate Day
deriving (SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
(SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool)
-> (SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool)
-> Eq SSFFirstPublicSimpleDate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
== :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
$c/= :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
/= :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
Eq, Eq SSFFirstPublicSimpleDate
Eq SSFFirstPublicSimpleDate =>
(SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Ordering)
-> (SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool)
-> (SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool)
-> (SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool)
-> (SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool)
-> (SSFFirstPublicSimpleDate
-> SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate)
-> (SSFFirstPublicSimpleDate
-> SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate)
-> Ord SSFFirstPublicSimpleDate
SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Ordering
SSFFirstPublicSimpleDate
-> SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate
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 :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Ordering
compare :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Ordering
$c< :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
< :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
$c<= :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
<= :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
$c> :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
> :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
$c>= :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
>= :: SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate -> Bool
$cmax :: SSFFirstPublicSimpleDate
-> SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate
max :: SSFFirstPublicSimpleDate
-> SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate
$cmin :: SSFFirstPublicSimpleDate
-> SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate
min :: SSFFirstPublicSimpleDate
-> SSFFirstPublicSimpleDate -> SSFFirstPublicSimpleDate
Ord, (forall x.
SSFFirstPublicSimpleDate -> Rep SSFFirstPublicSimpleDate x)
-> (forall x.
Rep SSFFirstPublicSimpleDate x -> SSFFirstPublicSimpleDate)
-> Generic SSFFirstPublicSimpleDate
forall x.
Rep SSFFirstPublicSimpleDate x -> SSFFirstPublicSimpleDate
forall x.
SSFFirstPublicSimpleDate -> Rep SSFFirstPublicSimpleDate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SSFFirstPublicSimpleDate -> Rep SSFFirstPublicSimpleDate x
from :: forall x.
SSFFirstPublicSimpleDate -> Rep SSFFirstPublicSimpleDate x
$cto :: forall x.
Rep SSFFirstPublicSimpleDate x -> SSFFirstPublicSimpleDate
to :: forall x.
Rep SSFFirstPublicSimpleDate x -> SSFFirstPublicSimpleDate
Generic)
instance Makeable SSFFirstPublicSimpleDate where
make :: forall (m :: * -> *).
MonadFail m =>
Text -> m SSFFirstPublicSimpleDate
make Text
x = do
case Bool -> TimeLocale -> [Char] -> [Char] -> Maybe Day
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> [Char] -> [Char] -> m t
parseTimeM Bool
False TimeLocale
defaultTimeLocale [Char]
"%Y-%-m-%-d" (Text -> [Char]
T.unpack Text
x) :: Maybe Day of
Maybe Day
Nothing -> [Char] -> m SSFFirstPublicSimpleDate
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFFirstPublicSimpleDate)
-> [Char] -> m SSFFirstPublicSimpleDate
forall a b. (a -> b) -> a -> b
$ [Char]
"first_public date " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
T.unpack Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" is not a correct date in the format YYYY-MM-DD."
Just Day
d -> SSFFirstPublicSimpleDate -> m SSFFirstPublicSimpleDate
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Day -> SSFFirstPublicSimpleDate
SSFFirstPublicSimpleDate Day
d)
instance Suspicious SSFFirstPublicSimpleDate where inspect :: SSFFirstPublicSimpleDate -> Maybe [[Char]]
inspect SSFFirstPublicSimpleDate
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFFirstPublicSimpleDate where
show :: SSFFirstPublicSimpleDate -> [Char]
show (SSFFirstPublicSimpleDate Day
x) = TimeLocale -> [Char] -> Day -> [Char]
forall t. FormatTime t => TimeLocale -> [Char] -> t -> [Char]
formatTime TimeLocale
defaultTimeLocale [Char]
"%Y-%-m-%-d" Day
x
instance Csv.ToField SSFFirstPublicSimpleDate where
toField :: SSFFirstPublicSimpleDate -> Field
toField (SSFFirstPublicSimpleDate Day
x) = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ Day -> [Char]
forall a. Show a => a -> [Char]
show Day
x
instance Csv.FromField SSFFirstPublicSimpleDate where
parseField :: Field -> Parser SSFFirstPublicSimpleDate
parseField = [Char] -> Field -> Parser SSFFirstPublicSimpleDate
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"first_public"
newtype SSFLastUpdatedSimpleDate = SSFLastUpdatedSimpleDate Day
deriving (SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
(SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool)
-> (SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool)
-> Eq SSFLastUpdatedSimpleDate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
== :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
$c/= :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
/= :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
Eq, Eq SSFLastUpdatedSimpleDate
Eq SSFLastUpdatedSimpleDate =>
(SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Ordering)
-> (SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool)
-> (SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool)
-> (SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool)
-> (SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool)
-> (SSFLastUpdatedSimpleDate
-> SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate)
-> (SSFLastUpdatedSimpleDate
-> SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate)
-> Ord SSFLastUpdatedSimpleDate
SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Ordering
SSFLastUpdatedSimpleDate
-> SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate
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 :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Ordering
compare :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Ordering
$c< :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
< :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
$c<= :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
<= :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
$c> :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
> :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
$c>= :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
>= :: SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate -> Bool
$cmax :: SSFLastUpdatedSimpleDate
-> SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate
max :: SSFLastUpdatedSimpleDate
-> SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate
$cmin :: SSFLastUpdatedSimpleDate
-> SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate
min :: SSFLastUpdatedSimpleDate
-> SSFLastUpdatedSimpleDate -> SSFLastUpdatedSimpleDate
Ord, (forall x.
SSFLastUpdatedSimpleDate -> Rep SSFLastUpdatedSimpleDate x)
-> (forall x.
Rep SSFLastUpdatedSimpleDate x -> SSFLastUpdatedSimpleDate)
-> Generic SSFLastUpdatedSimpleDate
forall x.
Rep SSFLastUpdatedSimpleDate x -> SSFLastUpdatedSimpleDate
forall x.
SSFLastUpdatedSimpleDate -> Rep SSFLastUpdatedSimpleDate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SSFLastUpdatedSimpleDate -> Rep SSFLastUpdatedSimpleDate x
from :: forall x.
SSFLastUpdatedSimpleDate -> Rep SSFLastUpdatedSimpleDate x
$cto :: forall x.
Rep SSFLastUpdatedSimpleDate x -> SSFLastUpdatedSimpleDate
to :: forall x.
Rep SSFLastUpdatedSimpleDate x -> SSFLastUpdatedSimpleDate
Generic)
instance Makeable SSFLastUpdatedSimpleDate where
make :: forall (m :: * -> *).
MonadFail m =>
Text -> m SSFLastUpdatedSimpleDate
make Text
x = do
case Bool -> TimeLocale -> [Char] -> [Char] -> Maybe Day
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> [Char] -> [Char] -> m t
parseTimeM Bool
False TimeLocale
defaultTimeLocale [Char]
"%Y-%-m-%-d" (Text -> [Char]
T.unpack Text
x) :: Maybe Day of
Maybe Day
Nothing -> [Char] -> m SSFLastUpdatedSimpleDate
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFLastUpdatedSimpleDate)
-> [Char] -> m SSFLastUpdatedSimpleDate
forall a b. (a -> b) -> a -> b
$ [Char]
"last_updated date " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
T.unpack Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" is not a correct date in the format YYYY-MM-DD."
Just Day
d -> SSFLastUpdatedSimpleDate -> m SSFLastUpdatedSimpleDate
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Day -> SSFLastUpdatedSimpleDate
SSFLastUpdatedSimpleDate Day
d)
instance Suspicious SSFLastUpdatedSimpleDate where inspect :: SSFLastUpdatedSimpleDate -> Maybe [[Char]]
inspect SSFLastUpdatedSimpleDate
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFLastUpdatedSimpleDate where
show :: SSFLastUpdatedSimpleDate -> [Char]
show (SSFLastUpdatedSimpleDate Day
x) = TimeLocale -> [Char] -> Day -> [Char]
forall t. FormatTime t => TimeLocale -> [Char] -> t -> [Char]
formatTime TimeLocale
defaultTimeLocale [Char]
"%Y-%-m-%-d" Day
x
instance Csv.ToField SSFLastUpdatedSimpleDate where
toField :: SSFLastUpdatedSimpleDate -> Field
toField (SSFLastUpdatedSimpleDate Day
x) = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ Day -> [Char]
forall a. Show a => a -> [Char]
show Day
x
instance Csv.FromField SSFLastUpdatedSimpleDate where
parseField :: Field -> Parser SSFLastUpdatedSimpleDate
parseField = [Char] -> Field -> Parser SSFLastUpdatedSimpleDate
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"last_updated"
newtype SSFInstrumentModel = SSFInstrumentModel T.Text deriving (SSFInstrumentModel -> SSFInstrumentModel -> Bool
(SSFInstrumentModel -> SSFInstrumentModel -> Bool)
-> (SSFInstrumentModel -> SSFInstrumentModel -> Bool)
-> Eq SSFInstrumentModel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
== :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
$c/= :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
/= :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
Eq, Eq SSFInstrumentModel
Eq SSFInstrumentModel =>
(SSFInstrumentModel -> SSFInstrumentModel -> Ordering)
-> (SSFInstrumentModel -> SSFInstrumentModel -> Bool)
-> (SSFInstrumentModel -> SSFInstrumentModel -> Bool)
-> (SSFInstrumentModel -> SSFInstrumentModel -> Bool)
-> (SSFInstrumentModel -> SSFInstrumentModel -> Bool)
-> (SSFInstrumentModel -> SSFInstrumentModel -> SSFInstrumentModel)
-> (SSFInstrumentModel -> SSFInstrumentModel -> SSFInstrumentModel)
-> Ord SSFInstrumentModel
SSFInstrumentModel -> SSFInstrumentModel -> Bool
SSFInstrumentModel -> SSFInstrumentModel -> Ordering
SSFInstrumentModel -> SSFInstrumentModel -> SSFInstrumentModel
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 :: SSFInstrumentModel -> SSFInstrumentModel -> Ordering
compare :: SSFInstrumentModel -> SSFInstrumentModel -> Ordering
$c< :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
< :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
$c<= :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
<= :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
$c> :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
> :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
$c>= :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
>= :: SSFInstrumentModel -> SSFInstrumentModel -> Bool
$cmax :: SSFInstrumentModel -> SSFInstrumentModel -> SSFInstrumentModel
max :: SSFInstrumentModel -> SSFInstrumentModel -> SSFInstrumentModel
$cmin :: SSFInstrumentModel -> SSFInstrumentModel -> SSFInstrumentModel
min :: SSFInstrumentModel -> SSFInstrumentModel -> SSFInstrumentModel
Ord)
$(makeInstances ''SSFInstrumentModel "instrument_model")
newtype SSFLibraryLayout = SSFLibraryLayout T.Text deriving (SSFLibraryLayout -> SSFLibraryLayout -> Bool
(SSFLibraryLayout -> SSFLibraryLayout -> Bool)
-> (SSFLibraryLayout -> SSFLibraryLayout -> Bool)
-> Eq SSFLibraryLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
== :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
$c/= :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
/= :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
Eq, Eq SSFLibraryLayout
Eq SSFLibraryLayout =>
(SSFLibraryLayout -> SSFLibraryLayout -> Ordering)
-> (SSFLibraryLayout -> SSFLibraryLayout -> Bool)
-> (SSFLibraryLayout -> SSFLibraryLayout -> Bool)
-> (SSFLibraryLayout -> SSFLibraryLayout -> Bool)
-> (SSFLibraryLayout -> SSFLibraryLayout -> Bool)
-> (SSFLibraryLayout -> SSFLibraryLayout -> SSFLibraryLayout)
-> (SSFLibraryLayout -> SSFLibraryLayout -> SSFLibraryLayout)
-> Ord SSFLibraryLayout
SSFLibraryLayout -> SSFLibraryLayout -> Bool
SSFLibraryLayout -> SSFLibraryLayout -> Ordering
SSFLibraryLayout -> SSFLibraryLayout -> SSFLibraryLayout
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 :: SSFLibraryLayout -> SSFLibraryLayout -> Ordering
compare :: SSFLibraryLayout -> SSFLibraryLayout -> Ordering
$c< :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
< :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
$c<= :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
<= :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
$c> :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
> :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
$c>= :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
>= :: SSFLibraryLayout -> SSFLibraryLayout -> Bool
$cmax :: SSFLibraryLayout -> SSFLibraryLayout -> SSFLibraryLayout
max :: SSFLibraryLayout -> SSFLibraryLayout -> SSFLibraryLayout
$cmin :: SSFLibraryLayout -> SSFLibraryLayout -> SSFLibraryLayout
min :: SSFLibraryLayout -> SSFLibraryLayout -> SSFLibraryLayout
Ord)
$(makeInstances ''SSFLibraryLayout "library_layout")
newtype SSFLibrarySource = SSFLibrarySource T.Text deriving (SSFLibrarySource -> SSFLibrarySource -> Bool
(SSFLibrarySource -> SSFLibrarySource -> Bool)
-> (SSFLibrarySource -> SSFLibrarySource -> Bool)
-> Eq SSFLibrarySource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFLibrarySource -> SSFLibrarySource -> Bool
== :: SSFLibrarySource -> SSFLibrarySource -> Bool
$c/= :: SSFLibrarySource -> SSFLibrarySource -> Bool
/= :: SSFLibrarySource -> SSFLibrarySource -> Bool
Eq, Eq SSFLibrarySource
Eq SSFLibrarySource =>
(SSFLibrarySource -> SSFLibrarySource -> Ordering)
-> (SSFLibrarySource -> SSFLibrarySource -> Bool)
-> (SSFLibrarySource -> SSFLibrarySource -> Bool)
-> (SSFLibrarySource -> SSFLibrarySource -> Bool)
-> (SSFLibrarySource -> SSFLibrarySource -> Bool)
-> (SSFLibrarySource -> SSFLibrarySource -> SSFLibrarySource)
-> (SSFLibrarySource -> SSFLibrarySource -> SSFLibrarySource)
-> Ord SSFLibrarySource
SSFLibrarySource -> SSFLibrarySource -> Bool
SSFLibrarySource -> SSFLibrarySource -> Ordering
SSFLibrarySource -> SSFLibrarySource -> SSFLibrarySource
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 :: SSFLibrarySource -> SSFLibrarySource -> Ordering
compare :: SSFLibrarySource -> SSFLibrarySource -> Ordering
$c< :: SSFLibrarySource -> SSFLibrarySource -> Bool
< :: SSFLibrarySource -> SSFLibrarySource -> Bool
$c<= :: SSFLibrarySource -> SSFLibrarySource -> Bool
<= :: SSFLibrarySource -> SSFLibrarySource -> Bool
$c> :: SSFLibrarySource -> SSFLibrarySource -> Bool
> :: SSFLibrarySource -> SSFLibrarySource -> Bool
$c>= :: SSFLibrarySource -> SSFLibrarySource -> Bool
>= :: SSFLibrarySource -> SSFLibrarySource -> Bool
$cmax :: SSFLibrarySource -> SSFLibrarySource -> SSFLibrarySource
max :: SSFLibrarySource -> SSFLibrarySource -> SSFLibrarySource
$cmin :: SSFLibrarySource -> SSFLibrarySource -> SSFLibrarySource
min :: SSFLibrarySource -> SSFLibrarySource -> SSFLibrarySource
Ord)
$(makeInstances ''SSFLibrarySource "library_source")
newtype SSFInstrumentPlatform = SSFInstrumentPlatform T.Text deriving (SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
(SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool)
-> (SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool)
-> Eq SSFInstrumentPlatform
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
== :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
$c/= :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
/= :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
Eq, Eq SSFInstrumentPlatform
Eq SSFInstrumentPlatform =>
(SSFInstrumentPlatform -> SSFInstrumentPlatform -> Ordering)
-> (SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool)
-> (SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool)
-> (SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool)
-> (SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool)
-> (SSFInstrumentPlatform
-> SSFInstrumentPlatform -> SSFInstrumentPlatform)
-> (SSFInstrumentPlatform
-> SSFInstrumentPlatform -> SSFInstrumentPlatform)
-> Ord SSFInstrumentPlatform
SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
SSFInstrumentPlatform -> SSFInstrumentPlatform -> Ordering
SSFInstrumentPlatform
-> SSFInstrumentPlatform -> SSFInstrumentPlatform
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 :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Ordering
compare :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Ordering
$c< :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
< :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
$c<= :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
<= :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
$c> :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
> :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
$c>= :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
>= :: SSFInstrumentPlatform -> SSFInstrumentPlatform -> Bool
$cmax :: SSFInstrumentPlatform
-> SSFInstrumentPlatform -> SSFInstrumentPlatform
max :: SSFInstrumentPlatform
-> SSFInstrumentPlatform -> SSFInstrumentPlatform
$cmin :: SSFInstrumentPlatform
-> SSFInstrumentPlatform -> SSFInstrumentPlatform
min :: SSFInstrumentPlatform
-> SSFInstrumentPlatform -> SSFInstrumentPlatform
Ord)
$(makeInstances ''SSFInstrumentPlatform "instrument_platform")
newtype SSFLibraryName = SSFLibraryName T.Text deriving (SSFLibraryName -> SSFLibraryName -> Bool
(SSFLibraryName -> SSFLibraryName -> Bool)
-> (SSFLibraryName -> SSFLibraryName -> Bool) -> Eq SSFLibraryName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFLibraryName -> SSFLibraryName -> Bool
== :: SSFLibraryName -> SSFLibraryName -> Bool
$c/= :: SSFLibraryName -> SSFLibraryName -> Bool
/= :: SSFLibraryName -> SSFLibraryName -> Bool
Eq, Eq SSFLibraryName
Eq SSFLibraryName =>
(SSFLibraryName -> SSFLibraryName -> Ordering)
-> (SSFLibraryName -> SSFLibraryName -> Bool)
-> (SSFLibraryName -> SSFLibraryName -> Bool)
-> (SSFLibraryName -> SSFLibraryName -> Bool)
-> (SSFLibraryName -> SSFLibraryName -> Bool)
-> (SSFLibraryName -> SSFLibraryName -> SSFLibraryName)
-> (SSFLibraryName -> SSFLibraryName -> SSFLibraryName)
-> Ord SSFLibraryName
SSFLibraryName -> SSFLibraryName -> Bool
SSFLibraryName -> SSFLibraryName -> Ordering
SSFLibraryName -> SSFLibraryName -> SSFLibraryName
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 :: SSFLibraryName -> SSFLibraryName -> Ordering
compare :: SSFLibraryName -> SSFLibraryName -> Ordering
$c< :: SSFLibraryName -> SSFLibraryName -> Bool
< :: SSFLibraryName -> SSFLibraryName -> Bool
$c<= :: SSFLibraryName -> SSFLibraryName -> Bool
<= :: SSFLibraryName -> SSFLibraryName -> Bool
$c> :: SSFLibraryName -> SSFLibraryName -> Bool
> :: SSFLibraryName -> SSFLibraryName -> Bool
$c>= :: SSFLibraryName -> SSFLibraryName -> Bool
>= :: SSFLibraryName -> SSFLibraryName -> Bool
$cmax :: SSFLibraryName -> SSFLibraryName -> SSFLibraryName
max :: SSFLibraryName -> SSFLibraryName -> SSFLibraryName
$cmin :: SSFLibraryName -> SSFLibraryName -> SSFLibraryName
min :: SSFLibraryName -> SSFLibraryName -> SSFLibraryName
Ord)
$(makeInstances ''SSFLibraryName "library_name")
newtype SSFLibraryStrategy = SSFLibraryStrategy T.Text deriving (SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
(SSFLibraryStrategy -> SSFLibraryStrategy -> Bool)
-> (SSFLibraryStrategy -> SSFLibraryStrategy -> Bool)
-> Eq SSFLibraryStrategy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
== :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
$c/= :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
/= :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
Eq, Eq SSFLibraryStrategy
Eq SSFLibraryStrategy =>
(SSFLibraryStrategy -> SSFLibraryStrategy -> Ordering)
-> (SSFLibraryStrategy -> SSFLibraryStrategy -> Bool)
-> (SSFLibraryStrategy -> SSFLibraryStrategy -> Bool)
-> (SSFLibraryStrategy -> SSFLibraryStrategy -> Bool)
-> (SSFLibraryStrategy -> SSFLibraryStrategy -> Bool)
-> (SSFLibraryStrategy -> SSFLibraryStrategy -> SSFLibraryStrategy)
-> (SSFLibraryStrategy -> SSFLibraryStrategy -> SSFLibraryStrategy)
-> Ord SSFLibraryStrategy
SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
SSFLibraryStrategy -> SSFLibraryStrategy -> Ordering
SSFLibraryStrategy -> SSFLibraryStrategy -> SSFLibraryStrategy
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 :: SSFLibraryStrategy -> SSFLibraryStrategy -> Ordering
compare :: SSFLibraryStrategy -> SSFLibraryStrategy -> Ordering
$c< :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
< :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
$c<= :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
<= :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
$c> :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
> :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
$c>= :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
>= :: SSFLibraryStrategy -> SSFLibraryStrategy -> Bool
$cmax :: SSFLibraryStrategy -> SSFLibraryStrategy -> SSFLibraryStrategy
max :: SSFLibraryStrategy -> SSFLibraryStrategy -> SSFLibraryStrategy
$cmin :: SSFLibraryStrategy -> SSFLibraryStrategy -> SSFLibraryStrategy
min :: SSFLibraryStrategy -> SSFLibraryStrategy -> SSFLibraryStrategy
Ord)
$(makeInstances ''SSFLibraryStrategy "library_strategy")
newtype SSFFastqFTPURI = SSFFastqFTPURI T.Text
deriving (SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
(SSFFastqFTPURI -> SSFFastqFTPURI -> Bool)
-> (SSFFastqFTPURI -> SSFFastqFTPURI -> Bool) -> Eq SSFFastqFTPURI
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
== :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
$c/= :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
/= :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
Eq, Eq SSFFastqFTPURI
Eq SSFFastqFTPURI =>
(SSFFastqFTPURI -> SSFFastqFTPURI -> Ordering)
-> (SSFFastqFTPURI -> SSFFastqFTPURI -> Bool)
-> (SSFFastqFTPURI -> SSFFastqFTPURI -> Bool)
-> (SSFFastqFTPURI -> SSFFastqFTPURI -> Bool)
-> (SSFFastqFTPURI -> SSFFastqFTPURI -> Bool)
-> (SSFFastqFTPURI -> SSFFastqFTPURI -> SSFFastqFTPURI)
-> (SSFFastqFTPURI -> SSFFastqFTPURI -> SSFFastqFTPURI)
-> Ord SSFFastqFTPURI
SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
SSFFastqFTPURI -> SSFFastqFTPURI -> Ordering
SSFFastqFTPURI -> SSFFastqFTPURI -> SSFFastqFTPURI
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 :: SSFFastqFTPURI -> SSFFastqFTPURI -> Ordering
compare :: SSFFastqFTPURI -> SSFFastqFTPURI -> Ordering
$c< :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
< :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
$c<= :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
<= :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
$c> :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
> :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
$c>= :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
>= :: SSFFastqFTPURI -> SSFFastqFTPURI -> Bool
$cmax :: SSFFastqFTPURI -> SSFFastqFTPURI -> SSFFastqFTPURI
max :: SSFFastqFTPURI -> SSFFastqFTPURI -> SSFFastqFTPURI
$cmin :: SSFFastqFTPURI -> SSFFastqFTPURI -> SSFFastqFTPURI
min :: SSFFastqFTPURI -> SSFFastqFTPURI -> SSFFastqFTPURI
Ord, (forall x. SSFFastqFTPURI -> Rep SSFFastqFTPURI x)
-> (forall x. Rep SSFFastqFTPURI x -> SSFFastqFTPURI)
-> Generic SSFFastqFTPURI
forall x. Rep SSFFastqFTPURI x -> SSFFastqFTPURI
forall x. SSFFastqFTPURI -> Rep SSFFastqFTPURI x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFFastqFTPURI -> Rep SSFFastqFTPURI x
from :: forall x. SSFFastqFTPURI -> Rep SSFFastqFTPURI x
$cto :: forall x. Rep SSFFastqFTPURI x -> SSFFastqFTPURI
to :: forall x. Rep SSFFastqFTPURI x -> SSFFastqFTPURI
Generic)
instance Makeable SSFFastqFTPURI where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFFastqFTPURI
make Text
x
| [Char] -> Bool
isURIReference (Text -> [Char]
T.unpack Text
x) = SSFFastqFTPURI -> m SSFFastqFTPURI
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SSFFastqFTPURI -> m SSFFastqFTPURI)
-> SSFFastqFTPURI -> m SSFFastqFTPURI
forall a b. (a -> b) -> a -> b
$ Text -> SSFFastqFTPURI
SSFFastqFTPURI Text
x
| Bool
otherwise = [Char] -> m SSFFastqFTPURI
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFFastqFTPURI) -> [Char] -> m SSFFastqFTPURI
forall a b. (a -> b) -> a -> b
$ [Char]
"fastq_ftp entry " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" is not a well-structured URI."
instance Suspicious SSFFastqFTPURI where inspect :: SSFFastqFTPURI -> Maybe [[Char]]
inspect SSFFastqFTPURI
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFFastqFTPURI where show :: SSFFastqFTPURI -> [Char]
show (SSFFastqFTPURI Text
x) = Text -> [Char]
T.unpack Text
x
instance Csv.ToField SSFFastqFTPURI where toField :: SSFFastqFTPURI -> Field
toField SSFFastqFTPURI
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFFastqFTPURI -> [Char]
forall a. Show a => a -> [Char]
show SSFFastqFTPURI
x
instance Csv.FromField SSFFastqFTPURI where parseField :: Field -> Parser SSFFastqFTPURI
parseField = [Char] -> Field -> Parser SSFFastqFTPURI
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"fastq_ftp"
newtype SSFFastqASPERAURI = SSFFastqASPERAURI T.Text
deriving (SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
(SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool)
-> (SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool)
-> Eq SSFFastqASPERAURI
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
== :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
$c/= :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
/= :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
Eq, Eq SSFFastqASPERAURI
Eq SSFFastqASPERAURI =>
(SSFFastqASPERAURI -> SSFFastqASPERAURI -> Ordering)
-> (SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool)
-> (SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool)
-> (SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool)
-> (SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool)
-> (SSFFastqASPERAURI -> SSFFastqASPERAURI -> SSFFastqASPERAURI)
-> (SSFFastqASPERAURI -> SSFFastqASPERAURI -> SSFFastqASPERAURI)
-> Ord SSFFastqASPERAURI
SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
SSFFastqASPERAURI -> SSFFastqASPERAURI -> Ordering
SSFFastqASPERAURI -> SSFFastqASPERAURI -> SSFFastqASPERAURI
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 :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Ordering
compare :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Ordering
$c< :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
< :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
$c<= :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
<= :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
$c> :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
> :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
$c>= :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
>= :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> Bool
$cmax :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> SSFFastqASPERAURI
max :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> SSFFastqASPERAURI
$cmin :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> SSFFastqASPERAURI
min :: SSFFastqASPERAURI -> SSFFastqASPERAURI -> SSFFastqASPERAURI
Ord, (forall x. SSFFastqASPERAURI -> Rep SSFFastqASPERAURI x)
-> (forall x. Rep SSFFastqASPERAURI x -> SSFFastqASPERAURI)
-> Generic SSFFastqASPERAURI
forall x. Rep SSFFastqASPERAURI x -> SSFFastqASPERAURI
forall x. SSFFastqASPERAURI -> Rep SSFFastqASPERAURI x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFFastqASPERAURI -> Rep SSFFastqASPERAURI x
from :: forall x. SSFFastqASPERAURI -> Rep SSFFastqASPERAURI x
$cto :: forall x. Rep SSFFastqASPERAURI x -> SSFFastqASPERAURI
to :: forall x. Rep SSFFastqASPERAURI x -> SSFFastqASPERAURI
Generic)
instance Makeable SSFFastqASPERAURI where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFFastqASPERAURI
make Text
x
| [Char] -> Bool
isURIReference (Text -> [Char]
T.unpack Text
x) = SSFFastqASPERAURI -> m SSFFastqASPERAURI
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SSFFastqASPERAURI -> m SSFFastqASPERAURI)
-> SSFFastqASPERAURI -> m SSFFastqASPERAURI
forall a b. (a -> b) -> a -> b
$ Text -> SSFFastqASPERAURI
SSFFastqASPERAURI Text
x
| Bool
otherwise = [Char] -> m SSFFastqASPERAURI
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFFastqASPERAURI) -> [Char] -> m SSFFastqASPERAURI
forall a b. (a -> b) -> a -> b
$ [Char]
"fastq_aspera entry " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" is not a well-structured URI."
instance Suspicious SSFFastqASPERAURI where inspect :: SSFFastqASPERAURI -> Maybe [[Char]]
inspect SSFFastqASPERAURI
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFFastqASPERAURI where show :: SSFFastqASPERAURI -> [Char]
show (SSFFastqASPERAURI Text
x) = Text -> [Char]
T.unpack Text
x
instance Csv.ToField SSFFastqASPERAURI where toField :: SSFFastqASPERAURI -> Field
toField SSFFastqASPERAURI
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFFastqASPERAURI -> [Char]
forall a. Show a => a -> [Char]
show SSFFastqASPERAURI
x
instance Csv.FromField SSFFastqASPERAURI where parseField :: Field -> Parser SSFFastqASPERAURI
parseField = [Char] -> Field -> Parser SSFFastqASPERAURI
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"fastq_aspera"
newtype SSFFastqBytes = SSFFastqBytes Integer deriving (SSFFastqBytes -> SSFFastqBytes -> Bool
(SSFFastqBytes -> SSFFastqBytes -> Bool)
-> (SSFFastqBytes -> SSFFastqBytes -> Bool) -> Eq SSFFastqBytes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFFastqBytes -> SSFFastqBytes -> Bool
== :: SSFFastqBytes -> SSFFastqBytes -> Bool
$c/= :: SSFFastqBytes -> SSFFastqBytes -> Bool
/= :: SSFFastqBytes -> SSFFastqBytes -> Bool
Eq, Eq SSFFastqBytes
Eq SSFFastqBytes =>
(SSFFastqBytes -> SSFFastqBytes -> Ordering)
-> (SSFFastqBytes -> SSFFastqBytes -> Bool)
-> (SSFFastqBytes -> SSFFastqBytes -> Bool)
-> (SSFFastqBytes -> SSFFastqBytes -> Bool)
-> (SSFFastqBytes -> SSFFastqBytes -> Bool)
-> (SSFFastqBytes -> SSFFastqBytes -> SSFFastqBytes)
-> (SSFFastqBytes -> SSFFastqBytes -> SSFFastqBytes)
-> Ord SSFFastqBytes
SSFFastqBytes -> SSFFastqBytes -> Bool
SSFFastqBytes -> SSFFastqBytes -> Ordering
SSFFastqBytes -> SSFFastqBytes -> SSFFastqBytes
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 :: SSFFastqBytes -> SSFFastqBytes -> Ordering
compare :: SSFFastqBytes -> SSFFastqBytes -> Ordering
$c< :: SSFFastqBytes -> SSFFastqBytes -> Bool
< :: SSFFastqBytes -> SSFFastqBytes -> Bool
$c<= :: SSFFastqBytes -> SSFFastqBytes -> Bool
<= :: SSFFastqBytes -> SSFFastqBytes -> Bool
$c> :: SSFFastqBytes -> SSFFastqBytes -> Bool
> :: SSFFastqBytes -> SSFFastqBytes -> Bool
$c>= :: SSFFastqBytes -> SSFFastqBytes -> Bool
>= :: SSFFastqBytes -> SSFFastqBytes -> Bool
$cmax :: SSFFastqBytes -> SSFFastqBytes -> SSFFastqBytes
max :: SSFFastqBytes -> SSFFastqBytes -> SSFFastqBytes
$cmin :: SSFFastqBytes -> SSFFastqBytes -> SSFFastqBytes
min :: SSFFastqBytes -> SSFFastqBytes -> SSFFastqBytes
Ord, (forall x. SSFFastqBytes -> Rep SSFFastqBytes x)
-> (forall x. Rep SSFFastqBytes x -> SSFFastqBytes)
-> Generic SSFFastqBytes
forall x. Rep SSFFastqBytes x -> SSFFastqBytes
forall x. SSFFastqBytes -> Rep SSFFastqBytes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFFastqBytes -> Rep SSFFastqBytes x
from :: forall x. SSFFastqBytes -> Rep SSFFastqBytes x
$cto :: forall x. Rep SSFFastqBytes x -> SSFFastqBytes
to :: forall x. Rep SSFFastqBytes x -> SSFFastqBytes
Generic)
instance Makeable SSFFastqBytes where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFFastqBytes
make Text
x =
case Reader Integer
forall a. Integral a => Reader a
T.decimal Text
x of
Left [Char]
e -> [Char] -> m SSFFastqBytes
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFFastqBytes) -> [Char] -> m SSFFastqBytes
forall a b. (a -> b) -> a -> b
$ [Char]
"fastq_bytes can not be converted to Integer because " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
e
Right (Integer
num, Text
"") -> SSFFastqBytes -> m SSFFastqBytes
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SSFFastqBytes -> m SSFFastqBytes)
-> SSFFastqBytes -> m SSFFastqBytes
forall a b. (a -> b) -> a -> b
$ Integer -> SSFFastqBytes
SSFFastqBytes Integer
num
Right (Integer
_, Text
rest) -> [Char] -> m SSFFastqBytes
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFFastqBytes) -> [Char] -> m SSFFastqBytes
forall a b. (a -> b) -> a -> b
$ [Char]
"fastq_bytes can not be converted to Integer, because of a trailing " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
rest
instance Suspicious SSFFastqBytes where inspect :: SSFFastqBytes -> Maybe [[Char]]
inspect SSFFastqBytes
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFFastqBytes where show :: SSFFastqBytes -> [Char]
show (SSFFastqBytes Integer
x) = Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
x
instance Csv.ToField SSFFastqBytes where toField :: SSFFastqBytes -> Field
toField (SSFFastqBytes Integer
x) = Integer -> Field
forall a. ToField a => a -> Field
Csv.toField Integer
x
instance Csv.FromField SSFFastqBytes where parseField :: Field -> Parser SSFFastqBytes
parseField = [Char] -> Field -> Parser SSFFastqBytes
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"fastq_bytes"
newtype SSFFastqMD5 = SSFFastqMD5 T.Text deriving (SSFFastqMD5 -> SSFFastqMD5 -> Bool
(SSFFastqMD5 -> SSFFastqMD5 -> Bool)
-> (SSFFastqMD5 -> SSFFastqMD5 -> Bool) -> Eq SSFFastqMD5
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
== :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
$c/= :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
/= :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
Eq, Eq SSFFastqMD5
Eq SSFFastqMD5 =>
(SSFFastqMD5 -> SSFFastqMD5 -> Ordering)
-> (SSFFastqMD5 -> SSFFastqMD5 -> Bool)
-> (SSFFastqMD5 -> SSFFastqMD5 -> Bool)
-> (SSFFastqMD5 -> SSFFastqMD5 -> Bool)
-> (SSFFastqMD5 -> SSFFastqMD5 -> Bool)
-> (SSFFastqMD5 -> SSFFastqMD5 -> SSFFastqMD5)
-> (SSFFastqMD5 -> SSFFastqMD5 -> SSFFastqMD5)
-> Ord SSFFastqMD5
SSFFastqMD5 -> SSFFastqMD5 -> Bool
SSFFastqMD5 -> SSFFastqMD5 -> Ordering
SSFFastqMD5 -> SSFFastqMD5 -> SSFFastqMD5
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 :: SSFFastqMD5 -> SSFFastqMD5 -> Ordering
compare :: SSFFastqMD5 -> SSFFastqMD5 -> Ordering
$c< :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
< :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
$c<= :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
<= :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
$c> :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
> :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
$c>= :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
>= :: SSFFastqMD5 -> SSFFastqMD5 -> Bool
$cmax :: SSFFastqMD5 -> SSFFastqMD5 -> SSFFastqMD5
max :: SSFFastqMD5 -> SSFFastqMD5 -> SSFFastqMD5
$cmin :: SSFFastqMD5 -> SSFFastqMD5 -> SSFFastqMD5
min :: SSFFastqMD5 -> SSFFastqMD5 -> SSFFastqMD5
Ord, (forall x. SSFFastqMD5 -> Rep SSFFastqMD5 x)
-> (forall x. Rep SSFFastqMD5 x -> SSFFastqMD5)
-> Generic SSFFastqMD5
forall x. Rep SSFFastqMD5 x -> SSFFastqMD5
forall x. SSFFastqMD5 -> Rep SSFFastqMD5 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFFastqMD5 -> Rep SSFFastqMD5 x
from :: forall x. SSFFastqMD5 -> Rep SSFFastqMD5 x
$cto :: forall x. Rep SSFFastqMD5 x -> SSFFastqMD5
to :: forall x. Rep SSFFastqMD5 x -> SSFFastqMD5
Generic)
instance Makeable SSFFastqMD5 where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFFastqMD5
make Text
x
| Text -> Bool
isMD5Hash Text
x = SSFFastqMD5 -> m SSFFastqMD5
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SSFFastqMD5 -> m SSFFastqMD5) -> SSFFastqMD5 -> m SSFFastqMD5
forall a b. (a -> b) -> a -> b
$ Text -> SSFFastqMD5
SSFFastqMD5 Text
x
| Bool
otherwise = [Char] -> m SSFFastqMD5
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFFastqMD5) -> [Char] -> m SSFFastqMD5
forall a b. (a -> b) -> a -> b
$ [Char]
"fastq_md5 " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" does not contain a well-structured MD5 hash"
isMD5Hash :: T.Text -> Bool
isMD5Hash :: Text -> Bool
isMD5Hash Text
x = Text -> Int
T.length Text
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
32 Bool -> Bool -> Bool
&& (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isHexDigit Text
x
instance Suspicious SSFFastqMD5 where inspect :: SSFFastqMD5 -> Maybe [[Char]]
inspect SSFFastqMD5
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFFastqMD5 where show :: SSFFastqMD5 -> [Char]
show (SSFFastqMD5 Text
x) = Text -> [Char]
T.unpack Text
x
instance Csv.ToField SSFFastqMD5 where toField :: SSFFastqMD5 -> Field
toField SSFFastqMD5
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFFastqMD5 -> [Char]
forall a. Show a => a -> [Char]
show SSFFastqMD5
x
instance Csv.FromField SSFFastqMD5 where parseField :: Field -> Parser SSFFastqMD5
parseField = [Char] -> Field -> Parser SSFFastqMD5
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"fastq_md5"
newtype SSFReadCount = SSFReadCount Integer deriving (SSFReadCount -> SSFReadCount -> Bool
(SSFReadCount -> SSFReadCount -> Bool)
-> (SSFReadCount -> SSFReadCount -> Bool) -> Eq SSFReadCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFReadCount -> SSFReadCount -> Bool
== :: SSFReadCount -> SSFReadCount -> Bool
$c/= :: SSFReadCount -> SSFReadCount -> Bool
/= :: SSFReadCount -> SSFReadCount -> Bool
Eq, Eq SSFReadCount
Eq SSFReadCount =>
(SSFReadCount -> SSFReadCount -> Ordering)
-> (SSFReadCount -> SSFReadCount -> Bool)
-> (SSFReadCount -> SSFReadCount -> Bool)
-> (SSFReadCount -> SSFReadCount -> Bool)
-> (SSFReadCount -> SSFReadCount -> Bool)
-> (SSFReadCount -> SSFReadCount -> SSFReadCount)
-> (SSFReadCount -> SSFReadCount -> SSFReadCount)
-> Ord SSFReadCount
SSFReadCount -> SSFReadCount -> Bool
SSFReadCount -> SSFReadCount -> Ordering
SSFReadCount -> SSFReadCount -> SSFReadCount
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 :: SSFReadCount -> SSFReadCount -> Ordering
compare :: SSFReadCount -> SSFReadCount -> Ordering
$c< :: SSFReadCount -> SSFReadCount -> Bool
< :: SSFReadCount -> SSFReadCount -> Bool
$c<= :: SSFReadCount -> SSFReadCount -> Bool
<= :: SSFReadCount -> SSFReadCount -> Bool
$c> :: SSFReadCount -> SSFReadCount -> Bool
> :: SSFReadCount -> SSFReadCount -> Bool
$c>= :: SSFReadCount -> SSFReadCount -> Bool
>= :: SSFReadCount -> SSFReadCount -> Bool
$cmax :: SSFReadCount -> SSFReadCount -> SSFReadCount
max :: SSFReadCount -> SSFReadCount -> SSFReadCount
$cmin :: SSFReadCount -> SSFReadCount -> SSFReadCount
min :: SSFReadCount -> SSFReadCount -> SSFReadCount
Ord, (forall x. SSFReadCount -> Rep SSFReadCount x)
-> (forall x. Rep SSFReadCount x -> SSFReadCount)
-> Generic SSFReadCount
forall x. Rep SSFReadCount x -> SSFReadCount
forall x. SSFReadCount -> Rep SSFReadCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFReadCount -> Rep SSFReadCount x
from :: forall x. SSFReadCount -> Rep SSFReadCount x
$cto :: forall x. Rep SSFReadCount x -> SSFReadCount
to :: forall x. Rep SSFReadCount x -> SSFReadCount
Generic)
instance Makeable SSFReadCount where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFReadCount
make Text
x =
case Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
T.signed Reader Integer
forall a. Integral a => Reader a
T.decimal Text
x of
Left [Char]
e -> [Char] -> m SSFReadCount
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFReadCount) -> [Char] -> m SSFReadCount
forall a b. (a -> b) -> a -> b
$ [Char]
"read_count can not be converted to Integer because " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
e
Right (Integer
num, Text
"") ->
if Integer
num Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= -Integer
1
then SSFReadCount -> m SSFReadCount
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> SSFReadCount
SSFReadCount Integer
num)
else [Char] -> m SSFReadCount
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFReadCount) -> [Char] -> m SSFReadCount
forall a b. (a -> b) -> a -> b
$ [Char]
"read_count " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" not >0."
Right (Integer
_, Text
rest) -> [Char] -> m SSFReadCount
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFReadCount) -> [Char] -> m SSFReadCount
forall a b. (a -> b) -> a -> b
$ [Char]
"read_count can not be converted to Integer, because of a trailing " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
rest
instance Suspicious SSFReadCount where
inspect :: SSFReadCount -> Maybe [[Char]]
inspect (SSFReadCount Integer
x)
| Integer
x Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== -Integer
1 = [[Char]] -> Maybe [[Char]]
forall a. a -> Maybe a
Just [[Char]
"read_count is set to -1, which indicates a missing value."]
| Bool
otherwise = [[Char]] -> Maybe [[Char]]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance Show SSFReadCount where show :: SSFReadCount -> [Char]
show (SSFReadCount Integer
x) = Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
x
instance Csv.ToField SSFReadCount where toField :: SSFReadCount -> Field
toField (SSFReadCount Integer
x) = Integer -> Field
forall a. ToField a => a -> Field
Csv.toField Integer
x
instance Csv.FromField SSFReadCount where parseField :: Field -> Parser SSFReadCount
parseField = [Char] -> Field -> Parser SSFReadCount
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"read_count"
newtype SSFSubmittedFTPURI = SSFSubmittedFTPURI T.Text
deriving (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
(SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool)
-> (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool)
-> Eq SSFSubmittedFTPURI
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
== :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
$c/= :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
/= :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
Eq, Eq SSFSubmittedFTPURI
Eq SSFSubmittedFTPURI =>
(SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Ordering)
-> (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool)
-> (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool)
-> (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool)
-> (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool)
-> (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> SSFSubmittedFTPURI)
-> (SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> SSFSubmittedFTPURI)
-> Ord SSFSubmittedFTPURI
SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Ordering
SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> SSFSubmittedFTPURI
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 :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Ordering
compare :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Ordering
$c< :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
< :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
$c<= :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
<= :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
$c> :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
> :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
$c>= :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
>= :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> Bool
$cmax :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> SSFSubmittedFTPURI
max :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> SSFSubmittedFTPURI
$cmin :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> SSFSubmittedFTPURI
min :: SSFSubmittedFTPURI -> SSFSubmittedFTPURI -> SSFSubmittedFTPURI
Ord, (forall x. SSFSubmittedFTPURI -> Rep SSFSubmittedFTPURI x)
-> (forall x. Rep SSFSubmittedFTPURI x -> SSFSubmittedFTPURI)
-> Generic SSFSubmittedFTPURI
forall x. Rep SSFSubmittedFTPURI x -> SSFSubmittedFTPURI
forall x. SSFSubmittedFTPURI -> Rep SSFSubmittedFTPURI x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SSFSubmittedFTPURI -> Rep SSFSubmittedFTPURI x
from :: forall x. SSFSubmittedFTPURI -> Rep SSFSubmittedFTPURI x
$cto :: forall x. Rep SSFSubmittedFTPURI x -> SSFSubmittedFTPURI
to :: forall x. Rep SSFSubmittedFTPURI x -> SSFSubmittedFTPURI
Generic)
instance Makeable SSFSubmittedFTPURI where
make :: forall (m :: * -> *). MonadFail m => Text -> m SSFSubmittedFTPURI
make Text
x
| [Char] -> Bool
isURIReference (Text -> [Char]
T.unpack Text
x) = SSFSubmittedFTPURI -> m SSFSubmittedFTPURI
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SSFSubmittedFTPURI -> m SSFSubmittedFTPURI)
-> SSFSubmittedFTPURI -> m SSFSubmittedFTPURI
forall a b. (a -> b) -> a -> b
$ Text -> SSFSubmittedFTPURI
SSFSubmittedFTPURI Text
x
| Bool
otherwise = [Char] -> m SSFSubmittedFTPURI
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m SSFSubmittedFTPURI) -> [Char] -> m SSFSubmittedFTPURI
forall a b. (a -> b) -> a -> b
$ [Char]
"submitted_ftp entry " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" is not a well-structured URI."
instance Suspicious SSFSubmittedFTPURI where inspect :: SSFSubmittedFTPURI -> Maybe [[Char]]
inspect SSFSubmittedFTPURI
_ = Maybe [[Char]]
forall a. Maybe a
Nothing
instance Show SSFSubmittedFTPURI where show :: SSFSubmittedFTPURI -> [Char]
show (SSFSubmittedFTPURI Text
x) = Text -> [Char]
T.unpack Text
x
instance Csv.ToField SSFSubmittedFTPURI where toField :: SSFSubmittedFTPURI -> Field
toField SSFSubmittedFTPURI
x = [Char] -> Field
forall a. ToField a => a -> Field
Csv.toField ([Char] -> Field) -> [Char] -> Field
forall a b. (a -> b) -> a -> b
$ SSFSubmittedFTPURI -> [Char]
forall a. Show a => a -> [Char]
show SSFSubmittedFTPURI
x
instance Csv.FromField SSFSubmittedFTPURI where parseField :: Field -> Parser SSFSubmittedFTPURI
parseField = [Char] -> Field -> Parser SSFSubmittedFTPURI
forall a (m :: * -> *).
(MonadFail m, Makeable a, Typeable a) =>
[Char] -> Field -> m a
parseTypeCSV [Char]
"submitted_ftp"