Skip to content

Commit

Permalink
haddock fixed
Browse files Browse the repository at this point in the history
  • Loading branch information
konn committed Aug 8, 2014
1 parent 14f16d3 commit 412ab6d
Showing 1 changed file with 14 additions and 10 deletions.
24 changes: 14 additions & 10 deletions Algebra/Algorithms/ZeroDim.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
{-# LANGUAGE ConstraintKinds, DataKinds, DefaultSignatures, FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances, GADTs, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses, NoMonomorphismRestriction #-}
{-# LANGUAGE OverlappingInstances, OverloadedStrings, ParallelListComp #-}
{-# LANGUAGE PolyKinds, ScopedTypeVariables, StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell, TypeFamilies, TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ConstraintKinds, DataKinds, DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
{-# LANGUAGE NoMonomorphismRestriction, OverlappingInstances #-}
{-# LANGUAGE OverloadedStrings, ParallelListComp, PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, TemplateHaskell #-}
{-# LANGUAGE TypeFamilies, TypeSynonymInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -fwarn-name-shadowing #-}
-- | Algorithms for zero-dimensional ideals.
module Algebra.Algorithms.ZeroDim (univPoly, radical, isRadical, solveWith,
Expand Down Expand Up @@ -316,9 +316,13 @@ fglm ideal =
fglmMap :: forall k ord n. (Normed k, Ord k, Field k, IsMonomialOrder ord, IsPolynomial k n)
=> (OrderedPolynomial k ord (S n) -> V.Vector k)
-- ^ Linear map from polynomial ring.
-> ( [OrderedPolynomial k Lex (S n)] -- ^ lex-Groebner basis of the kernel of the given linear map.
, [OrderedPolynomial k Lex (S n)] -- ^ The vector basis of the image of the linear map.
)
-> ( [OrderedPolynomial k Lex (S n)]
, [OrderedPolynomial k Lex (S n)]
) -- ^ The tuple of:
--
-- * lex-Groebner basis of the kernel of the given linear map.
--
-- * The vector basis of the image of the linear map.
fglmMap l = runST $ do
env <- FGLMEnv l <$> newSTRef [] <*> newSTRef [] <*> newSTRef Nothing <*> newSTRef one
flip runReaderT env $ do
Expand Down

0 comments on commit 412ab6d

Please sign in to comment.