| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Horizon.Spec
Documentation
Constructors
| MkCabalFlag :: Flag Text -> CabalFlag |
newtype Compiler where Source #
Constructors
| MkCompiler | |
Fields
| |
Instances
| Generic (Flag a) Source # | |
| Show a => Show (Flag a) Source # | |
| FromDhall a => FromDhall (Flag a) Source # | |
Defined in Horizon.Spec Methods autoWith :: InputNormalizer -> Decoder (Flag a) # | |
| ToDhall a => ToDhall (Flag a) Source # | |
Defined in Horizon.Spec Methods injectWith :: InputNormalizer -> Encoder (Flag a) # | |
| Eq a => Eq (Flag a) Source # | |
| type Rep (Flag a) Source # | |
Defined in Horizon.Spec type Rep (Flag a) = D1 ('MetaData "Flag" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'False) (C1 ('MetaCons "Enable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Disable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |
Constructors
| MkGitSource | |
Instances
| Generic GitSource Source # | |
| Show GitSource Source # | |
| FromDhall GitSource Source # | |
Defined in Horizon.Spec Methods autoWith :: InputNormalizer -> Decoder GitSource # | |
| ToDhall GitSource Source # | |
Defined in Horizon.Spec Methods | |
| Eq GitSource Source # | |
| type Rep GitSource Source # | |
Defined in Horizon.Spec type Rep GitSource = D1 ('MetaData "GitSource" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'False) (C1 ('MetaCons "MkGitSource" 'PrefixI 'True) (S1 ('MetaSel ('Just "url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Repo) :*: (S1 ('MetaSel ('Just "revision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Revision) :*: S1 ('MetaSel ('Just "subdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Subdir))))) | |
data HackageSource where Source #
Constructors
| MkHackageSource | |
Fields
| |
Instances
| Generic HackageSource Source # | |
Defined in Horizon.Spec Associated Types type Rep HackageSource :: Type -> Type # | |
| Show HackageSource Source # | |
Defined in Horizon.Spec Methods showsPrec :: Int -> HackageSource -> ShowS # show :: HackageSource -> String # showList :: [HackageSource] -> ShowS # | |
| FromDhall HackageSource Source # | |
Defined in Horizon.Spec Methods | |
| ToDhall HackageSource Source # | |
Defined in Horizon.Spec Methods | |
| Eq HackageSource Source # | |
Defined in Horizon.Spec Methods (==) :: HackageSource -> HackageSource -> Bool # (/=) :: HackageSource -> HackageSource -> Bool # | |
| type Rep HackageSource Source # | |
Defined in Horizon.Spec type Rep HackageSource = D1 ('MetaData "HackageSource" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'False) (C1 ('MetaCons "MkHackageSource" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) | |
data HaskellPackage where Source #
Constructors
| MkHaskellPackage | |
Fields
| |
Instances
data HaskellSource where Source #
Constructors
| FromGit :: GitSource -> HaskellSource | |
| FromHackage :: HackageSource -> HaskellSource | |
| FromLocal :: LocalSource -> HaskellSource | |
| FromTarball :: TarballSource -> HaskellSource |
Instances
data HorizonExport where Source #
Constructors
| MakePackageSet :: PackageSetExportSettings -> HorizonExport | |
| MakeOverlay :: OverlayExportSettings -> HorizonExport |
Instances
newtype LocalSource where Source #
Constructors
| MkLocalSource | |
Fields
| |
Instances
| Generic LocalSource Source # | |
Defined in Horizon.Spec Associated Types type Rep LocalSource :: Type -> Type # | |
| Show LocalSource Source # | |
Defined in Horizon.Spec Methods showsPrec :: Int -> LocalSource -> ShowS # show :: LocalSource -> String # showList :: [LocalSource] -> ShowS # | |
| FromDhall LocalSource Source # | |
Defined in Horizon.Spec Methods | |
| ToDhall LocalSource Source # | |
Defined in Horizon.Spec Methods | |
| Eq LocalSource Source # | |
Defined in Horizon.Spec | |
| type Rep LocalSource Source # | |
Defined in Horizon.Spec type Rep LocalSource = D1 ('MetaData "LocalSource" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'True) (C1 ('MetaCons "MkLocalSource" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromLocalSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Subdir))) | |
Instances
data OverlayExportSettings where Source #
Constructors
| MkOverlayExportSettings | |
Fields
| |
Instances
newtype OverlayFile where Source #
Constructors
| MkOverlayFile | |
Fields
| |
Instances
| Generic OverlayFile Source # | |
Defined in Horizon.Spec Associated Types type Rep OverlayFile :: Type -> Type # | |
| Show OverlayFile Source # | |
Defined in Horizon.Spec Methods showsPrec :: Int -> OverlayFile -> ShowS # show :: OverlayFile -> String # showList :: [OverlayFile] -> ShowS # | |
| FromDhall OverlayFile Source # | |
Defined in Horizon.Spec Methods | |
| ToDhall OverlayFile Source # | |
Defined in Horizon.Spec Methods | |
| Eq OverlayFile Source # | |
Defined in Horizon.Spec | |
| type Rep OverlayFile Source # | |
Defined in Horizon.Spec type Rep OverlayFile = D1 ('MetaData "OverlayFile" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'True) (C1 ('MetaCons "MkOverlayFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromOverlayFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path Rel File)))) | |
newtype Overlay where Source #
Constructors
| MkOverlay | |
Fields
| |
Instances
| Generic Overlay Source # | |
| Show Overlay Source # | |
| FromDhall Overlay Source # | |
Defined in Horizon.Spec Methods autoWith :: InputNormalizer -> Decoder Overlay # | |
| ToDhall Overlay Source # | |
Defined in Horizon.Spec Methods injectWith :: InputNormalizer -> Encoder Overlay # | |
| Eq Overlay Source # | |
| type Rep Overlay Source # | |
Defined in Horizon.Spec type Rep Overlay = D1 ('MetaData "Overlay" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'True) (C1 ('MetaCons "MkOverlay" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromOverlay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageSet))) | |
newtype PackageList where Source #
Constructors
| MkPackageList | |
Fields
| |
Instances
| Generic PackageList Source # | |
Defined in Horizon.Spec Associated Types type Rep PackageList :: Type -> Type # | |
| Show PackageList Source # | |
Defined in Horizon.Spec Methods showsPrec :: Int -> PackageList -> ShowS # show :: PackageList -> String # showList :: [PackageList] -> ShowS # | |
| FromDhall PackageList Source # | |
Defined in Horizon.Spec Methods | |
| ToDhall PackageList Source # | |
Defined in Horizon.Spec Methods | |
| Eq PackageList Source # | |
Defined in Horizon.Spec | |
| type Rep PackageList Source # | |
Defined in Horizon.Spec type Rep PackageList = D1 ('MetaData "PackageList" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'True) (C1 ('MetaCons "MkPackageList" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromPackageList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Name HaskellPackage)))) | |
data PackageSetExportSettings where Source #
Constructors
| MkPackageSetExportSettings | |
Fields
| |
Instances
newtype PackageSetFile where Source #
Constructors
| MkPackageSetFile | |
Fields
| |
Instances
data PackageSet where Source #
Constructors
| MkPackageSet | |
Fields
| |
Instances
| Generic PackageSet Source # | |
Defined in Horizon.Spec Associated Types type Rep PackageSet :: Type -> Type # | |
| Show PackageSet Source # | |
Defined in Horizon.Spec Methods showsPrec :: Int -> PackageSet -> ShowS # show :: PackageSet -> String # showList :: [PackageSet] -> ShowS # | |
| FromDhall PackageSet Source # | |
Defined in Horizon.Spec Methods | |
| ToDhall PackageSet Source # | |
Defined in Horizon.Spec Methods | |
| Eq PackageSet Source # | |
Defined in Horizon.Spec | |
| type Rep PackageSet Source # | |
Defined in Horizon.Spec type Rep PackageSet = D1 ('MetaData "PackageSet" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'False) (C1 ('MetaCons "MkPackageSet" 'PrefixI 'True) (S1 ('MetaSel ('Just "compiler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Compiler) :*: S1 ('MetaSel ('Just "packages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageList))) | |
newtype PackagesDir where Source #
Constructors
| MkPackagesDir | |
Fields
| |
Instances
| Generic PackagesDir Source # | |
Defined in Horizon.Spec Associated Types type Rep PackagesDir :: Type -> Type # | |
| Show PackagesDir Source # | |
Defined in Horizon.Spec Methods showsPrec :: Int -> PackagesDir -> ShowS # show :: PackagesDir -> String # showList :: [PackagesDir] -> ShowS # | |
| FromDhall PackagesDir Source # | |
Defined in Horizon.Spec Methods | |
| ToDhall PackagesDir Source # | |
Defined in Horizon.Spec Methods | |
| Eq PackagesDir Source # | |
Defined in Horizon.Spec | |
| type Rep PackagesDir Source # | |
Defined in Horizon.Spec type Rep PackagesDir = D1 ('MetaData "PackagesDir" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'True) (C1 ('MetaCons "MkPackagesDir" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromPackagesDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path Rel Dir)))) | |
newtype Revision where Source #
Constructors
| MkRevision | |
Fields
| |
Constructors
| MkSubdir | |
Fields
| |
newtype TarballSource where Source #
Constructors
| MkTarballSource | |
Fields
| |
Instances
| Generic TarballSource Source # | |
Defined in Horizon.Spec Associated Types type Rep TarballSource :: Type -> Type # | |
| Show TarballSource Source # | |
Defined in Horizon.Spec Methods showsPrec :: Int -> TarballSource -> ShowS # show :: TarballSource -> String # showList :: [TarballSource] -> ShowS # | |
| FromDhall TarballSource Source # | |
Defined in Horizon.Spec Methods | |
| ToDhall TarballSource Source # | |
Defined in Horizon.Spec Methods | |
| Eq TarballSource Source # | |
Defined in Horizon.Spec Methods (==) :: TarballSource -> TarballSource -> Bool # (/=) :: TarballSource -> TarballSource -> Bool # | |
| type Rep TarballSource Source # | |
Defined in Horizon.Spec type Rep TarballSource = D1 ('MetaData "TarballSource" "Horizon.Spec" "horizon-spec-0.6-1qjyHv1rWUuGCO8m0qFcnR" 'True) (C1 ('MetaCons "MkTarballSource" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromTarballSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Url))) | |
Constructors
| MkVersion | |
Fields
| |