More polishing

This commit is contained in:
Oliver Charles 2021-02-28 20:09:46 +00:00
parent e444782554
commit b566190419
9 changed files with 546 additions and 618 deletions

View File

@ -34,14 +34,7 @@ library
Rel8
Rel8.Text
other-modules:
Rel8.Column
Rel8.ColumnSchema
Rel8.DBEq
Rel8.EqTable
Rel8.Expr
Rel8.Optimize
Rel8.Query
Rel8.TableSchema
test-suite tests

File diff suppressed because it is too large Load Diff

View File

@ -1,7 +0,0 @@
{-# language AllowAmbiguousTypes #-}
{-# language ConstraintKinds #-}
{-# language RankNTypes #-}
{-# language TypeFamilies #-}
{-# language UndecidableInstances #-}
module Rel8.Column where

View File

@ -1,56 +0,0 @@
{-# language GeneralizedNewtypeDeriving #-}
{-# language KindSignatures #-}
module Rel8.ColumnSchema ( ColumnSchema(..) ) where
import Data.Kind
import Data.String
{-| The schema for a column in a table. To construct values of this type,
enable the @OverloadedStrings@ language extension and write literal Haskell
strings:
@
\{\-\# LANGUAGE OverloadedStrings -\}
tableSchema :: TableSchema ( HaskellPackage ColumnSchema )
tableSchema =
TableSchema
{ ...
, tableColumns =
HaskallPackage
{ packageName = "name" -- Here "name" :: ColumnSchema due to OverloadedStrings
}
}
@
If you want to programatically create @ColumnSchema@'s, you can use
'Data.String.fromString':
@
import Data.String ( fromString )
commonPrefix :: String
commonPrefix = "prefix_"
tableSchema :: TableSchema ( HaskellPackage ColumnSchema )
tableSchema =
TableSchema
{ ...
, tableColumns =
HaskallPackage
{ packageName = fromString ( prefix ++ "name" )
}
}
@
-}
newtype ColumnSchema ( a :: Type ) =
ColumnSchema { columnName :: String }
-- | You can construct @ColumnSchema@ values by using @\{\-\# LANGUAGE OverloadedStrings #-\}@ and writing
-- literal strings in your source code.
instance IsString ( ColumnSchema a ) where
fromString =
ColumnSchema

View File

@ -1,3 +0,0 @@
module Rel8.DBEq where

View File

@ -1,14 +0,0 @@
{-# language BlockArguments #-}
{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language ScopedTypeVariables #-}
{-# language TypeApplications #-}
{-# language TypeFamilies #-}
{-# language UndecidableInstances #-}
{-# language UndecidableSuperClasses #-}
module Rel8.EqTable where
import Rel8

View File

@ -1,21 +0,0 @@
{-# language BlockArguments #-}
{-# language DataKinds #-}
{-# language DefaultSignatures #-}
{-# language DeriveAnyClass #-}
{-# language DeriveGeneric #-}
{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language GADTs #-}
{-# language MultiParamTypeClasses #-}
{-# language NamedFieldPuns #-}
{-# language RoleAnnotations #-}
{-# language ScopedTypeVariables #-}
{-# language TypeApplications #-}
{-# language TypeFamilies #-}
{-# language UndecidableInstances #-}
{-# language UndecidableSuperClasses #-}
module Rel8.Expr where

View File

@ -1,27 +0,0 @@
{-# language ApplicativeDo #-}
{-# language BlockArguments #-}
{-# language DeriveGeneric #-}
{-# language DisambiguateRecordFields #-}
{-# language DuplicateRecordFields #-}
{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language GADTs #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# language KindSignatures #-}
{-# language LambdaCase #-}
{-# language MultiParamTypeClasses #-}
{-# language NamedFieldPuns #-}
{-# language RankNTypes #-}
{-# language ScopedTypeVariables #-}
{-# language TypeApplications #-}
{-# language TypeFamilies #-}
{-# language TypeOperators #-}
{-# language UndecidableInstances #-}
{-# language UndecidableSuperClasses #-}
{-# options -fno-warn-deprecations #-}
module Rel8.Query where

View File

@ -1,67 +0,0 @@
{-# language DeriveFunctor #-}
{-# language KindSignatures #-}
{-# language NamedFieldPuns #-}
{-# options -fno-warn-deprecations #-}
module Rel8.TableSchema where
import Data.Kind
import qualified Opaleye.Internal.Table as Opaleye
{-| The schema for a table. This is used to specify the name and schema
that a table belongs to (the @FROM@ part of a SQL query), along with
the schema of the columns within this table.
For each selectable table in your database, you should provide a @TableSchema@
in order to interact with the table via Rel8. For a table storing a list of
Haskell packages (as defined in the example for 'Rel8.Column.Column'), we would
write:
@
haskellPackage :: TableSchema ( HaskellPackage 'Rel8.ColumnSchema.ColumnSchema' )
haskellPackage =
TableSchema
{ tableName = "haskell_package"
, tableSchema = Nothing -- Assumes that haskell_package is reachable from your connections search_path
, tableColumns =
HaskellPackage { packageName = "name"
, packageAuthor = "author"
}
}
@
-}
data TableSchema ( schema :: Type ) =
TableSchema
{ tableName :: String
-- ^ The name of the table.
, tableSchema :: Maybe String
-- ^ The schema that this table belongs to. If 'Nothing', whatever is on
-- the connection's @search_path@ will be used.
, tableColumns :: schema
-- ^ The columns of the table. Typically you would use a a higher-kinded
-- data type here, parameterized by the 'Rel8.ColumnSchema.ColumnSchema' functor.
}
deriving
( Functor )
toOpaleyeTable
:: TableSchema schema
-> Opaleye.Writer write view
-> Opaleye.View view
-> Opaleye.Table write view
toOpaleyeTable TableSchema{ tableName, tableSchema } writer view =
case tableSchema of
Nothing ->
Opaleye.Table tableName tableFields
Just s ->
Opaleye.TableWithSchema s tableName tableFields
where
tableFields =
Opaleye.TableFields writer view