Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Ribosome.App.Data
Documentation
newtype ProjectName Source #
Constructors
ProjectName | |
Fields |
Instances
IsString ProjectName Source # | |
Defined in Ribosome.App.Data Methods fromString :: String -> ProjectName # | |
Show ProjectName Source # | |
Defined in Ribosome.App.Data Methods showsPrec :: Int -> ProjectName -> ShowS # show :: ProjectName -> String # showList :: [ProjectName] -> ShowS # | |
Eq ProjectName Source # | |
Defined in Ribosome.App.Data | |
Ord ProjectName Source # | |
Defined in Ribosome.App.Data Methods compare :: ProjectName -> ProjectName -> Ordering # (<) :: ProjectName -> ProjectName -> Bool # (<=) :: ProjectName -> ProjectName -> Bool # (>) :: ProjectName -> ProjectName -> Bool # (>=) :: ProjectName -> ProjectName -> Bool # max :: ProjectName -> ProjectName -> ProjectName # min :: ProjectName -> ProjectName -> ProjectName # |
newtype ModuleName Source #
Constructors
ModuleName | |
Fields
|
Instances
IsString ModuleName Source # | |
Defined in Ribosome.App.Data Methods fromString :: String -> ModuleName # | |
Show ModuleName Source # | |
Defined in Ribosome.App.Data Methods showsPrec :: Int -> ModuleName -> ShowS # show :: ModuleName -> String # showList :: [ModuleName] -> ShowS # | |
Eq ModuleName Source # | |
Defined in Ribosome.App.Data | |
Ord ModuleName Source # | |
Defined in Ribosome.App.Data Methods compare :: ModuleName -> ModuleName -> Ordering # (<) :: ModuleName -> ModuleName -> Bool # (<=) :: ModuleName -> ModuleName -> Bool # (>) :: ModuleName -> ModuleName -> Bool # (>=) :: ModuleName -> ModuleName -> Bool # max :: ModuleName -> ModuleName -> ModuleName # min :: ModuleName -> ModuleName -> ModuleName # |
data ProjectNames Source #
Constructors
ProjectNames | |
Fields
|
Instances
Constructors
GithubOrg | |
Fields
|
Instances
IsString GithubOrg Source # | |
Defined in Ribosome.App.Data Methods fromString :: String -> GithubOrg # | |
Show GithubOrg Source # | |
Eq GithubOrg Source # | |
Ord GithubOrg Source # | |
newtype GithubRepo Source #
Constructors
GithubRepo | |
Fields
|
Instances
IsString GithubRepo Source # | |
Defined in Ribosome.App.Data Methods fromString :: String -> GithubRepo # | |
Show GithubRepo Source # | |
Defined in Ribosome.App.Data Methods showsPrec :: Int -> GithubRepo -> ShowS # show :: GithubRepo -> String # showList :: [GithubRepo] -> ShowS # | |
Eq GithubRepo Source # | |
Defined in Ribosome.App.Data | |
Ord GithubRepo Source # | |
Defined in Ribosome.App.Data Methods compare :: GithubRepo -> GithubRepo -> Ordering # (<) :: GithubRepo -> GithubRepo -> Bool # (<=) :: GithubRepo -> GithubRepo -> Bool # (>) :: GithubRepo -> GithubRepo -> Bool # (>=) :: GithubRepo -> GithubRepo -> Bool # max :: GithubRepo -> GithubRepo -> GithubRepo # min :: GithubRepo -> GithubRepo -> GithubRepo # |
newtype CachixName Source #
Constructors
CachixName | |
Fields
|
Instances
IsString CachixName Source # | |
Defined in Ribosome.App.Data Methods fromString :: String -> CachixName # | |
Show CachixName Source # | |
Defined in Ribosome.App.Data Methods showsPrec :: Int -> CachixName -> ShowS # show :: CachixName -> String # showList :: [CachixName] -> ShowS # | |
Eq CachixName Source # | |
Defined in Ribosome.App.Data | |
Ord CachixName Source # | |
Defined in Ribosome.App.Data Methods compare :: CachixName -> CachixName -> Ordering # (<) :: CachixName -> CachixName -> Bool # (<=) :: CachixName -> CachixName -> Bool # (>) :: CachixName -> CachixName -> Bool # (>=) :: CachixName -> CachixName -> Bool # max :: CachixName -> CachixName -> CachixName # min :: CachixName -> CachixName -> CachixName # |
Constructors
CachixKey | |
Fields
|
Instances
IsString CachixKey Source # | |
Defined in Ribosome.App.Data Methods fromString :: String -> CachixKey # | |
Show CachixKey Source # | |
Eq CachixKey Source # | |
Ord CachixKey Source # | |
newtype SkipCachix Source #
Constructors
SkipCachix | |
Fields
|
Instances
Show SkipCachix Source # | |
Defined in Ribosome.App.Data Methods showsPrec :: Int -> SkipCachix -> ShowS # show :: SkipCachix -> String # showList :: [SkipCachix] -> ShowS # | |
Default SkipCachix Source # | |
Defined in Ribosome.App.Data Methods def :: SkipCachix # | |
Eq SkipCachix Source # | |
Defined in Ribosome.App.Data |
Constructors
FlakeUrl | |
Fields
|
newtype Maintainer Source #
Constructors
Maintainer | |
Fields
|
Instances
IsString Maintainer Source # | |
Defined in Ribosome.App.Data Methods fromString :: String -> Maintainer # | |
Show Maintainer Source # | |
Defined in Ribosome.App.Data Methods showsPrec :: Int -> Maintainer -> ShowS # show :: Maintainer -> String # showList :: [Maintainer] -> ShowS # | |
Eq Maintainer Source # | |
Defined in Ribosome.App.Data | |
Ord Maintainer Source # | |
Defined in Ribosome.App.Data Methods compare :: Maintainer -> Maintainer -> Ordering # (<) :: Maintainer -> Maintainer -> Bool # (<=) :: Maintainer -> Maintainer -> Bool # (>) :: Maintainer -> Maintainer -> Bool # (>=) :: Maintainer -> Maintainer -> Bool # max :: Maintainer -> Maintainer -> Maintainer # min :: Maintainer -> Maintainer -> Maintainer # |
Constructors
PrintDir | |
Fields
|
Constructors
Github | |
Fields
|
Instances
Generic Github Source # | |
Show Github Source # | |
Eq Github Source # | |
type Rep Github Source # | |
Defined in Ribosome.App.Data type Rep Github = D1 ('MetaData "Github" "Ribosome.App.Data" "ribosome-app-0.9.9.9-BawzhNaYTQG6T4bsxTOKy4" 'False) (C1 ('MetaCons "Github" 'PrefixI 'True) (S1 ('MetaSel ('Just "org") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GithubOrg) :*: S1 ('MetaSel ('Just "repo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GithubRepo))) |
Constructors
Cachix | |
Fields |
Instances
Generic Cachix Source # | |
Show Cachix Source # | |
Eq Cachix Source # | |
type Rep Cachix Source # | |
Defined in Ribosome.App.Data type Rep Cachix = D1 ('MetaData "Cachix" "Ribosome.App.Data" "ribosome-app-0.9.9.9-BawzhNaYTQG6T4bsxTOKy4" 'False) (C1 ('MetaCons "Cachix" 'PrefixI 'True) (S1 ('MetaSel ('Just "cachixName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CachixName) :*: S1 ('MetaSel ('Just "cachixKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CachixKey))) |
Constructors
Project | |
Instances
Generic Project Source # | |
Show Project Source # | |
Eq Project Source # | |
type Rep Project Source # | |
Defined in Ribosome.App.Data type Rep Project = D1 ('MetaData "Project" "Ribosome.App.Data" "ribosome-app-0.9.9.9-BawzhNaYTQG6T4bsxTOKy4" 'False) (C1 ('MetaCons "Project" 'PrefixI 'True) ((S1 ('MetaSel ('Just "names") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectNames) :*: S1 ('MetaSel ('Just "github") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Github))) :*: (S1 ('MetaSel ('Just "cachix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Cachix)) :*: (S1 ('MetaSel ('Just "directory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path Abs Dir)) :*: S1 ('MetaSel ('Just "branch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Branch))))) |
Instances
Generic Global Source # | |
Show Global Source # | |
Default Global Source # | |
Defined in Ribosome.App.Data | |
Eq Global Source # | |
type Rep Global Source # | |
Defined in Ribosome.App.Data type Rep Global = D1 ('MetaData "Global" "Ribosome.App.Data" "ribosome-app-0.9.9.9-BawzhNaYTQG6T4bsxTOKy4" 'False) (C1 ('MetaCons "Global" 'PrefixI 'True) (S1 ('MetaSel ('Just "quiet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "force") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) |
data NewProject Source #
Constructors
NewProject | |
Fields
|