1#############################################################################
2##
3##  OtherFunctors.gi                                  Graded Modules package
4##
5##  Copyright 2007-2010, Mohamed Barakat, University of Kaiserslautern
6##                       Markus Lange-Hegermann, RWTH Aachen
7##
8##  Implementation stuff for some other graded functors.
9##
10#############################################################################
11
12####################################
13#
14# install global functions/variables:
15#
16####################################
17
18##
19## DirectSum
20##
21
22InstallGlobalFunction( _Functor_DirectSum_OnGradedModules,	### defines: DirectSum
23  function( M, N )
24    local S, degMN, sum, iotaM, iotaN, piM, piN, natural, phi;
25
26    CheckIfTheyLieInTheSameCategory( M, N );
27
28    S := HomalgRing( M );
29
30    degMN := Concatenation( DegreesOfGenerators( M ), DegreesOfGenerators( N ) );
31
32    #degMN := List( degMN, HomalgElementToInteger  );
33
34    sum := DirectSum( UnderlyingModule( M ), UnderlyingModule( N ) );
35
36    # take the non-graded natural transformations
37    iotaM := MonoOfLeftSummand( sum );
38    iotaN:= MonoOfRightSummand( sum );
39    piM := EpiOnLeftFactor( sum );
40    piN := EpiOnRightFactor( sum );
41
42    # create the graded sum with the help of its natural generalized embedding
43    natural := NaturalGeneralizedEmbedding( sum );
44    natural := GradedMap( natural, "create", degMN, S );
45
46    Assert( 4, IsGeneralizedMorphismWithFullDomain( natural ) );
47    SetIsGeneralizedMorphismWithFullDomain( natural, true );
48
49    sum := Source( natural );
50    sum!.NaturalGeneralizedEmbedding := natural;
51
52    # grade the natural transformations
53    iotaM := GradedMap( iotaM, M, sum, S );
54    iotaN := GradedMap( iotaN, N, sum, S );
55    piM := GradedMap( piM, sum, M, S );
56    piN := GradedMap( piN, sum, N, S );
57
58    Assert( 4, IsMorphism( iotaM ) );
59    SetIsMorphism( iotaM, true );
60    Assert( 4, IsMorphism( iotaN ) );
61    SetIsMorphism( iotaN, true );
62    Assert( 4, IsMorphism( piM ) );
63    SetIsMorphism( piM, true );
64    Assert( 4, IsMorphism( piN ) );
65    SetIsMorphism( piN, true );
66
67    if HasIsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) and IsInt( IsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) ) and
68       HasIsModuleOfGlobalSectionsTruncatedAtCertainDegree( N ) and IsInt( IsModuleOfGlobalSectionsTruncatedAtCertainDegree( N ) ) and
69       IsModuleOfGlobalSectionsTruncatedAtCertainDegree( N ) = IsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) then
70        SetIsModuleOfGlobalSectionsTruncatedAtCertainDegree( sum, IsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) );
71    fi;
72
73    return SetPropertiesOfDirectSum( [ M, N ], sum, iotaM, iotaN, piM, piN );
74
75end );
76
77InstallValue( Functor_DirectSum_for_graded_modules,
78        CreateHomalgFunctor(
79                [ "name", "DirectSum" ],
80                [ "category", HOMALG_GRADED_MODULES.category ],
81                [ "operation", "DirectSumOp" ],
82                [ "natural_transformation1", "EpiOnLeftFactor" ],
83                [ "natural_transformation2", "EpiOnRightFactor" ],
84                [ "natural_transformation3", "MonoOfLeftSummand" ],
85                [ "natural_transformation4", "MonoOfRightSummand" ],
86                [ "number_of_arguments", 2 ],
87                [ "1", [ [ "covariant" ], HOMALG_GRADED_MODULES.FunctorOn ] ],
88                [ "2", [ [ "covariant" ], HOMALG_GRADED_MODULES.FunctorOn ] ],
89                [ "OnObjects", _Functor_DirectSum_OnGradedModules ],
90                [ "OnMorphismsHull", _Functor_DirectSum_OnMaps ]
91                )
92        );
93
94Functor_DirectSum_for_graded_modules!.ContainerForWeakPointersOnComputedBasicObjects := true;
95
96Functor_DirectSum_for_graded_modules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
97
98InstallFunctor( Functor_DirectSum_for_graded_modules );
99
100##
101## LinearPart
102##
103## (cf. Eisenbud, Floystad, Schreyer: Sheaf Cohomology and Free Resolutions over Exterior Algebras)
104
105InstallGlobalFunction( _Functor_LinearPart_OnGradedModules,    ### defines: LinearPart (object part)
106  function( M )
107    return M;
108end );
109
110##
111InstallGlobalFunction( _Functor_LinearPart_OnGradedMaps, ### defines: LinearPart (morphism part)
112  function( F_source, F_target, arg_before_pos, phi, arg_behind_pos )
113    local deg_s, deg_t, S, zero, mat, deg, i, j, result;
114
115    if HasIsZero( phi ) and IsZero( phi ) then
116        return phi;
117    fi;
118
119    deg_s := Set( DegreesOfGenerators( F_source ) );
120    deg_t := Set( DegreesOfGenerators( F_source ) );
121    if Length( deg_s ) = 1 and Length( deg_t ) = 1 and deg_s[1] = deg_t[1] - 1 then
122        return phi;
123    fi;
124
125    S := HomalgRing( phi );
126
127    zero := Zero( S );
128
129    mat := ShallowCopy( MatrixOfMap( phi ) );
130
131    SetIsMutableMatrix( mat, true );
132
133    deg := DegreesOfEntries( mat );
134
135    if not ( deg <> [] and IsHomogeneousList( deg ) and IsHomogeneousList( deg[1] ) and IsInt( deg[1][1] ) ) then
136      Error( "Multigraduations are not yet supported" );
137    fi;
138
139    for i in [ 1 .. Length( deg ) ] do
140      for j in [ 1 .. Length( deg[1] ) ] do
141        if deg[i][j] <> -1 then
142          mat[ i, j ] := zero;
143        fi;
144      od;
145    od;
146
147    MakeImmutable( mat );
148
149    result := GradedMap( mat, F_source, F_target );
150
151    if HasIsMorphism( phi ) and IsMorphism( phi ) then
152        Assert( 4, IsMorphism( result ) );
153        SetIsMorphism( result, true );
154    fi;
155
156    return result;
157
158end );
159
160InstallValue( Functor_LinearPart_ForGradedModules,
161        CreateHomalgFunctor(
162                [ "name", "LinearPart" ],
163                [ "category", HOMALG_GRADED_MODULES.category ],
164                [ "operation", "LinearPart" ],
165                [ "number_of_arguments", 1 ],
166                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], HOMALG_GRADED_MODULES.FunctorOn ] ],
167                [ "OnObjects", _Functor_LinearPart_OnGradedModules ],
168                [ "OnMorphisms", _Functor_LinearPart_OnGradedMaps ]
169                )
170        );
171
172Functor_LinearPart_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
173
174Functor_LinearPart_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
175
176InstallFunctor( Functor_LinearPart_ForGradedModules );
177
178##
179## ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree
180##
181
182InstallGlobalFunction( _Functor_ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree_OnGradedModules,
183  function( d, M )
184  local S, deg, l, mat, pi;
185
186    S := HomalgRing( M );
187
188    if NrRelations( M ) <> 0 then
189        Error( "This functor only accepts graded free modules" );
190    fi;
191
192    deg := List( DegreesOfGenerators( M ), HomalgElementToInteger );
193    l := Filtered( [ 1 .. Length( deg ) ], a -> deg[a] = d );
194
195    if IsHomalgLeftObjectOrMorphismOfLeftObjects( M ) then
196        mat := CertainRows( HomalgIdentityMatrix( NrGenerators( M ), S ), l );
197    else
198        mat := CertainColumns( HomalgIdentityMatrix( NrGenerators( M ), S ), l );
199    fi;
200
201    pi := GradedMap( mat, ListWithIdenticalEntries( Length( l ), d ), M );
202
203    Assert( 4, IsMorphism( pi ) );
204    SetIsMorphism( pi, true );
205
206    if l = [ 1 .. Length( deg ) ] then
207        Assert( 3, IsEpimorphism( pi ) );
208        SetIsEpimorphism( pi, true );
209    fi;
210    Assert( 3, IsMonomorphism( pi ) );
211    SetIsMonomorphism( pi, true );
212
213    return pi;
214
215end );
216
217InstallValue( Functor_ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree_ForGradedModules,
218        CreateHomalgFunctor(
219                [ "name", "ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree" ],
220                [ "category", HOMALG_GRADED_MODULES.category ],
221                [ "operation", "ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree" ],
222                [ "number_of_arguments", 1 ],
223                [ "0", [ IsInt ] ],
224                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], HOMALG_GRADED_MODULES.FunctorOn ] ],
225                [ "OnObjects", _Functor_ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree_OnGradedModules ]
226                )
227        );
228
229Functor_ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
230
231Functor_ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
232
233InstallFunctor( Functor_ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree_ForGradedModules );
234
235InstallMethod( ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree,
236               "for homalg elements",
237               [ IsHomalgElement, IsHomalgGradedModule ],
238
239  function( d, M )
240
241    return ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree( HomalgElementToInteger( d ), M );
242
243end );
244
245## DirectSummandOfGradedFreeModuleGeneratedByACertainDegree
246
247InstallMethod( DirectSummandOfGradedFreeModuleGeneratedByACertainDegree,
248        "for linear complexes over the exterior algebra",
249        [ IsInt, IsGradedModuleRep ],
250  function( m, M )
251    local pi, N;
252
253    pi := ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree( m, M );
254
255    N := Source( pi );
256
257    return N;
258
259end );
260
261InstallMethod( DirectSummandOfGradedFreeModuleGeneratedByACertainDegree,
262        "for linear complexes over the exterior algebra",
263        [ IsInt, IsInt, IsMapOfGradedModulesRep ],
264  function( m, n, phi )
265    local pi1, pi2, pi2_minus_1;
266
267    pi1 := ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree( m, Source( phi ) );
268    pi2 := ProjectionToDirectSummandOfGradedFreeModuleGeneratedByACertainDegree( n, Range( phi ) );
269
270    # PostInverse of a SubidentityMatrix is a GAP-computation
271    pi2_minus_1 := PostInverse( pi2 );
272
273    return PreCompose( PreCompose( pi1, phi ), pi2_minus_1 );
274
275end );
276
277InstallMethod( DirectSummandOfGradedFreeModuleGeneratedByACertainDegree,
278               "for homalg elements",
279               [ IsHomalgElement, IsHomalgGradedModule ],
280
281  function( d, M )
282
283    return DirectSummandOfGradedFreeModuleGeneratedByACertainDegree( HomalgElementToInteger( d ), M );
284
285end );
286
287InstallMethod( DirectSummandOfGradedFreeModuleGeneratedByACertainDegree,
288               "for homalg elements",
289               [ IsHomalgElement, IsHomalgElement, IsHomalgGradedMap ],
290
291  function( d1, d2, M )
292
293    return DirectSummandOfGradedFreeModuleGeneratedByACertainDegree( HomalgElementToInteger( d1 ), HomalgElementToInteger( d2 ), M );
294
295end );
296
297##
298## GeneralizedLinearStrand
299##
300
301InstallGlobalFunction( _Functor_GeneralizedLinearStrand_OnFreeCocomplexes,
302  function( f, T )
303  local i, alpha, alpha2, T2;
304
305    for i in MorphismDegreesOfComplex( T ) do
306
307        alpha := CertainMorphism( T, i );
308
309        alpha2 := DirectSummandOfGradedFreeModuleGeneratedByACertainDegree( f( i ), f( i + 1 ), alpha );
310
311        if not IsBound( T2 ) then
312            T2 := HomalgCocomplex( alpha2, i );
313        else
314            Add( T2, alpha2 );
315        fi;
316
317    od;
318
319    Assert( 3, IsComplex( T2 ) );
320    SetIsComplex( T2, true );
321
322    return T2;
323
324end );
325
326InstallGlobalFunction( _Functor_GeneralizedLinearStrand_OnCochainMaps,
327  function( F_source, F_target, arg_before_pos, phi, arg_behind_pos )
328    local f, i, alpha, f_i, alpha2, psi;
329
330    f := arg_before_pos[1];
331
332    for i in DegreesOfChainMorphism( phi ) do
333
334        alpha := CertainMorphism( phi, i );
335
336        f_i := f( i );
337
338        alpha2 := DirectSummandOfGradedFreeModuleGeneratedByACertainDegree( f_i, f_i, alpha );
339
340        if not IsBound( psi ) then
341            psi := HomalgChainMorphism( alpha2, F_source, F_target, i );
342        else
343            Add( psi, alpha2 );
344        fi;
345
346    od;
347
348    return psi;
349
350end );
351
352
353InstallValue( Functor_GeneralizedLinearStrand_ForGradedModules,
354        CreateHomalgFunctor(
355                [ "name", "GeneralizedLinearStrand" ],
356                [ "category", HOMALG_GRADED_MODULES.category ],
357                [ "operation", "GeneralizedLinearStrand" ],
358                [ "number_of_arguments", 1 ],
359                [ "0", [ IsFunction ] ],
360                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], [ IsHomalgComplex, IsHomalgChainMorphism ] ] ],
361                [ "OnObjects", _Functor_GeneralizedLinearStrand_OnFreeCocomplexes ],
362                [ "OnMorphisms", _Functor_GeneralizedLinearStrand_OnCochainMaps ]
363                )
364        );
365
366Functor_GeneralizedLinearStrand_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
367
368Functor_GeneralizedLinearStrand_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
369
370InstallFunctorOnObjects( Functor_GeneralizedLinearStrand_ForGradedModules );
371InstallFunctorOnMorphisms( Functor_GeneralizedLinearStrand_ForGradedModules );
372
373##
374## LinearStrand
375##
376
377# returns the subcomplex of a free complex,
378# where cohomological degree + shift = internal degree
379
380InstallGlobalFunction( _Functor_LinearStrand_OnFreeCocomplexes,
381  function( shift, T )
382
383    return GeneralizedLinearStrand( function( i ) return i + shift; end, T );
384
385end );
386
387InstallGlobalFunction( _Functor_LinearStrand_OnCochainMaps,
388  function( F_source, F_target, arg_before_pos, phi, arg_behind_pos )
389
390    return _Functor_GeneralizedLinearStrand_OnCochainMaps( F_source, F_target, [ function( i ) return i + arg_before_pos[1]; end ], phi, arg_behind_pos );
391
392end );
393
394
395InstallValue( Functor_LinearStrand_ForGradedModules,
396        CreateHomalgFunctor(
397                [ "name", "LinearStrand" ],
398                [ "category", HOMALG_GRADED_MODULES.category ],
399                [ "operation", "LinearStrand" ],
400                [ "number_of_arguments", 1 ],
401                [ "0", [ IsInt ] ],
402                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], [ IsHomalgComplex, IsHomalgChainMorphism ] ] ],
403                [ "OnObjects", _Functor_LinearStrand_OnFreeCocomplexes ],
404                [ "OnMorphisms", _Functor_LinearStrand_OnCochainMaps ]
405                )
406        );
407
408Functor_LinearStrand_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
409
410Functor_LinearStrand_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
411
412# InstallFunctor( Functor_LinearStrand_ForGradedModules );
413InstallFunctorOnObjects( Functor_LinearStrand_ForGradedModules );
414InstallFunctorOnMorphisms( Functor_LinearStrand_ForGradedModules );
415
416InstallMethod( LinearStrand,
417               "for homalg elements",
418               [ IsHomalgElement, IsHomalgMorphism ],
419
420  function( d, M )
421
422    return LinearStrand( HomalgElementToInteger( d ), M );
423
424end );
425
426##
427## ConstantStrand
428##
429
430InstallGlobalFunction( _Functor_ConstantStrand_OnFreeCocomplexes,
431  function( d, T )
432
433    return GeneralizedLinearStrand( function( i ) return d; end, T );
434
435end );
436
437InstallGlobalFunction( _Functor_ConstantStrand_OnCochainMaps,
438  function( F_source, F_target, arg_before_pos, phi, arg_behind_pos )
439
440    return _Functor_GeneralizedLinearStrand_OnCochainMaps( F_source, F_target, [ function( i ) return arg_before_pos[1]; end ], phi, arg_behind_pos );
441
442end );
443
444
445InstallValue( Functor_ConstantStrand_ForGradedModules,
446        CreateHomalgFunctor(
447                [ "name", "ConstantStrand" ],
448                [ "category", HOMALG_GRADED_MODULES.category ],
449                [ "operation", "ConstantStrand" ],
450                [ "number_of_arguments", 1 ],
451                [ "0", [ IsInt ] ],
452                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], [ IsHomalgComplex, IsHomalgChainMorphism ] ] ],
453                [ "OnObjects", _Functor_ConstantStrand_OnFreeCocomplexes ],
454                [ "OnMorphisms", _Functor_ConstantStrand_OnCochainMaps ]
455                )
456        );
457
458Functor_ConstantStrand_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
459
460Functor_ConstantStrand_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
461
462# InstallFunctor( Functor_ConstantStrand_ForGradedModules );
463InstallFunctorOnObjects( Functor_ConstantStrand_ForGradedModules );
464InstallFunctorOnMorphisms( Functor_ConstantStrand_ForGradedModules );
465
466InstallMethod( ConstantStrand,
467               "for homalg elements",
468               [ IsHomalgElement, IsHomalgMorphism ],
469
470  function( d, M )
471
472    return ConstantStrand( HomalgElementToInteger( d ), M );
473
474end );
475
476##
477## LinearFreeComplexOverExteriorAlgebraToModule
478##
479
480# This functor creates a module from a linear complex over the exterior algebra
481# (and a module map from a degree 0 cochain map).
482# first we introduce two helper functions
483
484##
485# Takes a linear map phi over a graded ring with indeterminates x_i
486# write phi = sum_i x_i*phi_i
487# returns (for left objects) the matrix
488# <phi_0,
489#  phi_1
490#
491#  phi_n>
492# and a map with matrix
493# <x_0*I,
494#  x_1*I
495#
496#  x_n*I>
497# where I is the identity matrix of size Source( phi ), i.e. both matrices have the same number of rows
498# later we will use these two maps to produce a pushout.
499InstallMethod( SplitLinearMapAccordingToIndeterminates,
500        "for linear complexes over the exterior algebra",
501        [ IsMapOfGradedModulesRep ],
502  function( phi )
503      local E, n, S, K, l_var, left, map_E, map_S, t, F, var_s_morphism, k, alpha, alpha2, matrix_of_extension, c, extension_matrix,l_test;
504
505      E := HomalgRing( phi );
506
507      n := Length( Indeterminates( E ) );
508
509      S := KoszulDualRing( E );
510
511      K := CoefficientsRing( E );
512
513      Assert( 5, IsIdenticalObj( K, CoefficientsRing( S ) ) );
514
515      l_var := Length( Indeterminates( S ) );
516
517      left := IsHomalgLeftObjectOrMorphismOfLeftObjects( phi );
518
519      if left then
520          map_E := MaximalIdealAsLeftMorphism( E );
521          map_S := MaximalIdealAsLeftMorphism( S );
522      else
523          map_E := MaximalIdealAsRightMorphism( E );
524          map_S := MaximalIdealAsRightMorphism( S );
525      fi;
526
527      t := NrGenerators( Range( phi ) );
528      if left then
529          if DegreesOfGenerators( Range( phi ) ) <> [ ] then
530              F := FreeLeftModuleWithDegrees( NrGenerators( Source( phi ) ), S, DegreesOfGenerators( Range( phi ) )[1] - 1 - n );
531          else
532              F := FreeLeftModuleWithDegrees( NrGenerators( Source( phi ) ), S, 0 );
533          fi;
534          var_s_morphism := - TensorProduct( map_S, F );
535      else
536          if DegreesOfGenerators( Range( phi ) ) <> [ ] then
537              F := FreeRightModuleWithDegrees( NrGenerators( Source( phi ) ), S, DegreesOfGenerators( Range( phi ) )[1] - 1 - n );
538          else
539              F := FreeRightModuleWithDegrees( NrGenerators( Source( phi ) ), S, 0 );
540          fi;
541          var_s_morphism := - TensorProduct( map_S, F );
542      fi;
543
544      alpha := TensorProduct( map_E, Range( phi ) );
545      alpha2 := GradedMap( HomalgIdentityMatrix( NrGenerators( Range( phi ) ), HomalgRing( phi ) ), Range( alpha ), Range( phi ) );
546      alpha := PreCompose( alpha, alpha2 );
547      matrix_of_extension := phi / alpha;
548      matrix_of_extension := K * MatrixOfMap( matrix_of_extension );
549      if left then
550          extension_matrix := HomalgZeroMatrix( 0, NrGenerators( Range( phi ) ), K );
551          for k in [ 1 .. l_var ] do
552              c := CertainColumns( matrix_of_extension, [ (k-1) * t + 1 .. k * t ] );
553              extension_matrix := UnionOfRowsOp( extension_matrix, c );
554          od;
555      else
556          extension_matrix := HomalgZeroMatrix( NrGenerators( Range( phi ) ), 0, K );
557          for k in [ 1 .. l_var ] do
558              c := CertainRows( matrix_of_extension, [ (k-1) * t + 1 .. k * t ] );
559              extension_matrix := UnionOfColumnsOp( extension_matrix, c );
560          od;
561      fi;
562
563      return [ extension_matrix, var_s_morphism ];
564
565end );
566
567##
568# Takes a linear map phi over a graded ring with indeterminates x_i
569# write phi = sum_i x_i*phi_i
570# creates (for left objects) the maps var_s_morphism and extension_map with matrices
571# <x_0*I,
572#  x_1*I
573#
574#  x_n*I>
575# and
576# <phi_0,
577#  phi_1
578#
579#  phi_n>
580# where I is the identity matrix of size Source( phi ),
581# i.e. both matrices have the same number of rows and (accordingly) both maps the same source.
582# The target of var_s_morphism is newly created
583# and of extension_map is taken to be the source of the second argument psi.
584# Then a base change is performed on source and target of extension_map, to have this
585# map (with a matrix with entries over the ground field) in a simple shape for later use.
586# In this process, a complement alpha of the image of extension_map is created (also for later use)
587# we return [ var_s_morphism, extension_map, alpha ]
588InstallMethod( ExtensionMapsFromExteriorComplex,
589        "for linear complexes over the exterior algebra",
590        [ IsMapOfGradedModulesRep, IsMapOfGradedModulesRep ],
591
592  function( phi, psi )
593      local N, E, S, K, extension_matrix, var_s_morphism, M, extension_map, alpha,l_test;
594
595      N := Source( psi );
596
597      E := HomalgRing( phi );
598
599      S := KoszulDualRing( E );
600
601      extension_matrix := SplitLinearMapAccordingToIndeterminates( phi );
602      var_s_morphism := extension_matrix[2];
603      M := Source( var_s_morphism );
604      extension_matrix := extension_matrix[1];
605
606      # compute over the free module instead of N, because it is faster
607      extension_map := GradedMap( S * extension_matrix, M, N, S );
608
609      if HasIsMorphism( phi ) and IsMorphism( phi ) then
610          Assert( 4, IsMorphism( extension_map ) );
611          SetIsMorphism( extension_map, true );
612      fi;
613
614      # This command changes the presentation of Source and Range of extension_map.
615      # In particular, N is changes, which was used before
616      # the change is due to the wish of a much faster ByASmallerPresentation
617      NormalizeGradedMorphism( extension_map );
618
619      alpha := extension_map!.complement_of_image;
620
621      return [ var_s_morphism, extension_map, alpha ];
622
623end );
624
625##
626# This method creates a module from a single linear map over the exterior algebra.
627# The idea behind this is, that the submodule of cohomology module generated by a certain degree
628# above the regularity can be constructed from this single map phi.
629# Let e_i be the generators of the exterior algebra and x_i the generators of the symmetric algebra.
630# Write phi=sum e_i*phi_i, then the phi_i are matrices over the ground field.
631# (Left modules) Let extension_map be the map with stacked matrix
632# <phi_0,
633#  phi_1
634#
635#  phi_n>
636# and var_s_morphism the map with stacked matrix
637# <x_0*I,
638#  x_1*I
639#
640#  x_n*I>
641# where I is the identity matrix of size Source( phi ).
642# (both maps have the same source)
643# Then cokernel( kernel( extension_map ) * var_s_morphism ) the the wanted module.
644InstallMethod( ModuleFromExtensionMap,
645        "for linear complexes over the exterior algebra",
646        [ IsMapOfGradedModulesRep ],
647
648  function( phi )
649      local  E, S, K, extension_matrix, var_s_morphism, M, ar, N, extension_map, result;
650
651      E := HomalgRing( phi );
652
653      S := KoszulDualRing( E );
654
655      if IsZero( phi ) then
656          if IsHomalgLeftObjectOrMorphismOfLeftObjects( phi ) then
657              return 0*S;
658          else
659              return S*0;
660          fi;
661      fi;
662
663      extension_matrix := SplitLinearMapAccordingToIndeterminates( phi );
664      var_s_morphism := extension_matrix[2];
665      M := Source( var_s_morphism );
666      extension_matrix := extension_matrix[1];
667
668      ar := [ NrGenerators( Range( phi ) ), S, DegreesOfGenerators( M )[1] ];
669      if IsHomalgLeftObjectOrMorphismOfLeftObjects( M ) then
670          N := CallFuncList( FreeLeftModuleWithDegrees, ar );
671      else
672          N := CallFuncList( FreeRightModuleWithDegrees, ar );
673      fi;
674      extension_map := GradedMap( S * extension_matrix, M, N, S );
675
676      if HasIsMorphism( phi ) and IsMorphism( phi ) then
677          Assert( 4, IsMorphism( extension_map ) );
678          SetIsMorphism( extension_map, true );
679      fi;
680
681      result := Cokernel( PreCompose( KernelEmb( extension_map ), var_s_morphism ) );
682
683      return result;
684
685end );
686
687InstallMethod( CompareArgumentsForLinearFreeComplexOverExteriorAlgebraToModuleOnObjects,
688        "for argument lists of the functor LinearFreeComplexOverExteriorAlgebraToModule on objects",
689        [ IsList, IsList ],
690
691  function( l_old, l_new )
692      local lower_bound1, lower_bound2;
693
694      lower_bound1 := Minimum( ObjectDegreesOfComplex( l_old[2] ) );
695      lower_bound2 := Minimum( ObjectDegreesOfComplex( l_new[2] ) );
696
697      return lower_bound1 = lower_bound2
698          and l_old[1] <= l_new[1]
699          and IsIdenticalObj(
700              CertainMorphism( l_old[2], lower_bound1 ),
701              CertainMorphism( l_new[2], lower_bound1 )
702              );
703
704end );
705
706InstallGlobalFunction( _Functor_LinearFreeComplexOverExteriorAlgebraToModule_OnGradedModules,
707  function( reg_sheaf, lin_tate )
708      local i, deg, A, n, S, k, result, EmbeddingsOfHigherDegrees, RecursiveEmbeddingsOfHigherDegrees, lower_bound, jj, j, tate_morphism, psi,
709      extension_map, var_s_morphism, T, T2, l, T2b, V1, V2, V1_iso_V2, isos, source_emb, map, certain_deg, t1, t2, phi, chain_phi, pos, Rresult, iso;
710
711      if not reg_sheaf < HomalgElementToInteger( HighestDegree( lin_tate ) ) then
712          Error( "the given regularity is larger than the number of morphisms in the complex" );
713      fi;
714      if not IsCocomplexOfFinitelyPresentedObjectsRep( lin_tate ) then
715          Error( "expected a _co_complex over the exterior algebra" );
716      fi;
717      for i in ObjectDegreesOfComplex( lin_tate ) do
718          deg := List( DegreesOfGenerators( CertainObject( lin_tate, i ) ), HomalgElementToInteger );
719          if not Length( Set( deg ) ) <= 1 then
720              Error( "for every cohomological degree in the cocomplex expected the degrees of generators of the object to be equal to each other" );
721          fi;
722#           if not ( deg = [] or deg[1] = i ) then
723#               Error( "expected the degrees of generators in the cocomplex to be equal to the cohomological degree" );
724#           fi;
725      od;
726
727      A := HomalgRing( lin_tate );
728
729      n:= Length( Indeterminates( A ) );
730
731      S := KoszulDualRing( A );
732
733      k := CoefficientsRing( A );
734
735      result := ModuleFromExtensionMap( CertainMorphism( lin_tate, reg_sheaf ) );
736
737#   each new step constructs a new StdM as pushout of
738#   extension_map*LeftPushoutMorphism  and  var_s_morphism.
739#   These maps are created from a modified Tate resolution.
740#
741#     StdM = new (+) old                                   Range( var_s_morphism )
742#             /\                                                  /\
743#             |                                                   |
744#             |                                                   |
745#             | LeftPushoutMorphism                               | var_s_morphism
746#             |                                                   |
747#             |           extension_map                           |
748#           new  <-------------------------------- Source( var_s_morphism ) = Source( extension_map )
749
750      result := Pushout( TheZeroMorphism( Zero( result ), result ), TheZeroMorphism( Zero( result ), Zero( result ) ) );
751
752      EmbeddingsOfHigherDegrees := rec( (String( reg_sheaf )) := TheIdentityMorphism( result ) );
753      RecursiveEmbeddingsOfHigherDegrees := rec( );
754
755      lower_bound := Minimum( ObjectDegreesOfComplex( lin_tate ) );
756
757      for jj in [ lower_bound + 1 .. reg_sheaf ] do
758          j := reg_sheaf + lower_bound - jj;
759
760          # create the extension map from the tate-resolution
761          # e.g. ( e_0, e_1, 3*e_0+2*e_1 ) leads to  /   1,   0,   3   \
762          #                                          \   0,   1,   2   /
763          # but the gaussian algorithm is applied to the latter matrix (both to rows an columns) for easier simplification
764          tate_morphism := CertainMorphism( lin_tate, j );
765
766          psi := LeftPushoutMorphism( result );
767
768          extension_map := ExtensionMapsFromExteriorComplex( tate_morphism, psi );
769          var_s_morphism := extension_map[1];
770          T := extension_map[3];
771          extension_map := extension_map[2];
772
773          # this line computes the global sections module
774          result := Pushout( var_s_morphism, PreCompose( extension_map, psi ) );
775
776          # This direct sum will be used in different contextes of the summands.
777          # We need to ensure that we speak about the same object in each of these cases.
778          # Thus, we force homalg to return this object regardless of the context of the summands.
779          Range( NaturalGeneralizedEmbedding( result ) )!.IgnoreContextOfArgumentsOfFunctor := true;
780          UnderlyingModule( Range( NaturalGeneralizedEmbedding( result ) ) )!.IgnoreContextOfArgumentsOfFunctor := true;
781
782          # the "old" ModuleOfGlobalSections (the one generated in larger degree) embeds into the new one
783          Assert( 3, IsMonomorphism( RightPushoutMorphism( result ) ) );
784          SetIsMonomorphism( RightPushoutMorphism( result ), true );
785
786          # the following block simplifies the ModuleOfGlobalSections much faster than ByASmallerPresentation could.
787          # We know in advance, which generators we need to generate result. These are
788          # 1) the new generators, i.e. Image( var_s_morphism ),
789          # 2) a basis of Cokernel( extension_map ) (which is free), i.e. Image( T ),
790          # 3) and the older generators, which have not been made superfluous, i.e. CertainGenerators( result, k ).
791          # We build the CoproductMorphism T2 of these three morphisms and its image is a smaller presentation of result
792          T := PreCompose( PreCompose( T, psi ), RightPushoutMorphism( result ) );
793          T2 := CoproductMorphism( LeftPushoutMorphism( result ), T );
794          l := PositionProperty( DegreesOfGenerators( result ), function( a ) return a > j+1; end );
795          if l <> fail then
796              l := [ l .. NrGenerators( result ) ];
797              T2b := GradedMap( CertainGenerators( result, l ), "free", result );
798              Assert( 4, IsMorphism( T2b ) );
799              SetIsMorphism( T2b, true );
800              T2 := CoproductMorphism( T2, T2b );
801          fi;
802          Assert( 3, IsMorphism( T2 ) );
803          SetIsMorphism( T2, true );
804          Assert( 3, IsEpimorphism( T2 ) );
805          SetIsEpimorphism( T2, true );
806          PushPresentationByIsomorphism( NaturalGeneralizedEmbedding( ImageObject( T2 ) ) );
807
808          # try to keep the information about higher modules
809          EmbeddingsOfHigherDegrees!.(String(j)) := TheIdentityMorphism( result );
810          for l in [ j + 1 .. reg_sheaf ] do
811              EmbeddingsOfHigherDegrees!.(String(l)) := PreCompose( EmbeddingsOfHigherDegrees!.(String(l)), RightPushoutMorphism( result ) );
812          od;
813          RecursiveEmbeddingsOfHigherDegrees!.(String(j+1)) := RightPushoutMorphism( result );
814
815      od;
816
817      # end core procedure
818
819      # Now set some properties of the module collected during the computation.
820      # Most of these are needed in the morphism part of this functor.
821
822      for l in [ lower_bound .. reg_sheaf ] do
823          if fail = GetFunctorObjCachedValue( Functor_TruncatedSubmodule_ForGradedModules, [ l, result ] ) then
824              SetFunctorObjCachedValue( Functor_TruncatedSubmodule_ForGradedModules, [ l, result ], FullSubobject( Source( EmbeddingsOfHigherDegrees!.(String(l)) ) ) );
825              SetNaturalTransformation( Functor_TruncatedSubmodule_ForGradedModules, [ l, result ], "TruncatedSubmoduleEmbed", EmbeddingsOfHigherDegrees!.(String(l)) );
826          fi;
827      od;
828      for l in [ lower_bound .. reg_sheaf - 1 ] do
829          if fail = GetFunctorObjCachedValue( Functor_TruncatedSubmoduleRecursiveEmbed_ForGradedModules, [ l, result ] ) then
830              SetFunctorObjCachedValue( Functor_TruncatedSubmoduleRecursiveEmbed_ForGradedModules, [ l, result ], RecursiveEmbeddingsOfHigherDegrees!.(String(l+1)) );
831          fi;
832      od;
833
834      isos := rec( );
835
836      for l in [ lower_bound .. reg_sheaf ] do
837
838          V1 := HomogeneousPartOverCoefficientsRing( l, CertainObject( lin_tate, l ) );
839
840          # modules of global sections truncated at different degrees do not share their V2 on purpose.
841          V1_iso_V2 := GradedMap( HomalgIdentityMatrix( NrGenerators( V1 ), k ), "free", V1 );
842          Assert( 4, IsMorphism( V1_iso_V2 ) );
843          SetIsMorphism( V1_iso_V2, true );
844          Assert( 4, IsIsomorphism( V1_iso_V2 ) );
845          SetIsIsomorphism( V1_iso_V2, true );
846          UpdateObjectsByMorphism( V1_iso_V2 );
847
848          isos.(l) := V1_iso_V2;
849
850          V2 := Source( V1_iso_V2 );
851
852          SetMapFromHomogenousPartOverSymmetricAlgebraToHomogeneousPartOverExteriorAlgebra( V2, V1_iso_V2 );
853          SetMapFromHomogenousPartOverExteriorAlgebraToHomogeneousPartOverSymmetricAlgebra( V1, V1_iso_V2 );
854
855          source_emb := Source( EmbeddingsOfHigherDegrees!.(String(l)) );
856
857          deg := List( DegreesOfGenerators( source_emb ), HomalgElementToInteger );
858          certain_deg := Filtered( [ 1 .. Length( deg ) ], a -> deg[a] = l );
859          if IsHomalgLeftObjectOrMorphismOfLeftObjects( result ) then
860              map := GradedMap( CertainRows( HomalgIdentityMatrix( NrGenerators( source_emb ), S ), certain_deg ), S * V2, source_emb );
861          else
862              map := GradedMap( CertainColumns( HomalgIdentityMatrix( NrGenerators( source_emb ), S ), certain_deg ), S * V2, source_emb );
863          fi;
864          Assert( 4, IsMorphism( map ) );
865          SetIsMorphism( map, true );
866
867          map := PreCompose( map, EmbeddingsOfHigherDegrees!.(String(l)) );
868
869          if fail = GetFunctorObjCachedValue( Functor_HomogeneousPartOverCoefficientsRing_ForGradedModules, [ l, result ] ) then
870              SetFunctorObjCachedValue( Functor_HomogeneousPartOverCoefficientsRing_ForGradedModules, [ l, result ], V2 );
871          fi;
872
873          SetNaturalTransformation(
874              Functor_HomogeneousPartOverCoefficientsRing_ForGradedModules,
875              [ l, result ],
876              "EmbeddingOfSubmoduleGeneratedByHomogeneousPart",
877              map
878          );
879
880          if l = lower_bound then
881              SetEmbeddingOfSubmoduleGeneratedByHomogeneousPart( V2, map );
882          fi;
883
884      od;
885
886      # set the koszul-right-adjoint matrices!
887      pos := PositionOfTheDefaultPresentation( result );
888      if not IsBound( result!.RepresentationMatricesOfKoszulId ) then
889          result!.RepresentationMatricesOfKoszulId := rec( );
890      fi;
891      if not IsBound( result!.RepresentationMatricesOfKoszulId!.(pos) ) then
892          result!.RepresentationMatricesOfKoszulId!.(pos) := rec( );
893      fi;
894      for l in MorphismDegreesOfComplex( lin_tate ) do
895          result!.RepresentationMatricesOfKoszulId!.(pos)!.(l) := MatrixOfMap( CertainMorphism( lin_tate, l ) );
896      od;
897
898      # this is now rather cheap, mostly the objects have to be created
899      Rresult := KoszulRightAdjoint( result, lower_bound, reg_sheaf );
900
901      for l in [ lower_bound .. reg_sheaf ] do
902
903          t1 := CertainObject( lin_tate, l );
904          t2 := CertainObject( Rresult, l ); # = omega_A * V2;
905
906          V1_iso_V2 := isos.(l);
907          V1 := Source( V1_iso_V2 );
908
909          iso := A^(-n) * ( A * V1_iso_V2^(-1) );
910
911          phi := GradedMap( HomalgIdentityMatrix( NrGenerators( t1 ), A ), t1, Source( iso ) );
912          Assert( 4, IsMorphism( phi ) );
913          SetIsMorphism( phi, true );
914          Assert( 4, IsIsomorphism( phi ) );
915          SetIsIsomorphism( phi, true );
916          UpdateObjectsByMorphism( phi );
917          phi := PreCompose( phi, iso );
918          phi := (-1)^l * phi;
919
920          if not IsBound( chain_phi ) then
921              chain_phi := HomalgChainMorphism( phi, lin_tate, Rresult, l );
922          else
923              Add( chain_phi, phi );
924          fi;
925
926      od;
927
928      SetNaturalMapFromExteriorComplexToRightAdjoint( lin_tate, chain_phi );
929
930      return result;
931
932end );
933
934InstallMethod( ConstructMorphismFromLayers,
935        "for argument lists of the functor LinearFreeComplexOverExteriorAlgebraToModule on objects",
936        [ IsGradedModuleRep, IsGradedModuleRep, IsHomalgChainMorphism ],
937
938  function( F_source, F_target, psi )
939    local reg, phi, lower_bound, jj, j, emb_new_source, emb_new_target, emb_old_source, emb_old_target, epi_source, epi_target, phi_new;
940
941    reg := HomalgElementToInteger( HighestDegree( psi ) );
942
943    phi := HighestDegreeMorphism( psi );
944
945    lower_bound := HomalgElementToInteger( LowestDegree( psi ) );
946
947    if reg = lower_bound then
948
949        phi := CompleteKernelSquare(
950            SubmoduleGeneratedByHomogeneousPart( lower_bound, F_source )!.map_having_subobject_as_its_image,
951            phi,
952            SubmoduleGeneratedByHomogeneousPart( lower_bound, F_target )!.map_having_subobject_as_its_image );
953
954    fi;
955
956    for jj in [ lower_bound + 1 .. reg ] do
957        j := reg + lower_bound - jj;
958
959        if j = reg - 1 then
960            emb_old_source := SubmoduleGeneratedByHomogeneousPartEmbed( j + 1, F_source ) / TruncatedSubmoduleEmbed( j, F_source );
961            emb_old_target := SubmoduleGeneratedByHomogeneousPartEmbed( j + 1, F_target ) / TruncatedSubmoduleEmbed( j, F_target );
962        else
963            emb_old_source := TruncatedSubmoduleRecursiveEmbed( j, F_source );
964            emb_old_target := TruncatedSubmoduleRecursiveEmbed( j, F_target );
965        fi;
966
967        emb_new_source := SubmoduleGeneratedByHomogeneousPartEmbed( j, F_source ) / TruncatedSubmoduleEmbed( j, F_source );
968        emb_new_target := SubmoduleGeneratedByHomogeneousPartEmbed( j, F_target ) / TruncatedSubmoduleEmbed( j, F_target );
969
970        epi_source := CoproductMorphism( emb_new_source, -emb_old_source );
971        epi_target := CoproductMorphism( emb_new_target, -emb_old_target );
972
973        Assert( 3, IsMorphism( epi_source ) );
974        SetIsMorphism( epi_source, true );
975        Assert( 3, IsEpimorphism( epi_source ) );
976        SetIsEpimorphism( epi_source, true );
977
978        Assert( 3, IsMorphism( epi_target ) );
979        SetIsMorphism( epi_target, true );
980        Assert( 3, IsEpimorphism( epi_target ) );
981        SetIsEpimorphism( epi_target, true );
982
983        phi_new := CertainMorphism( psi, j );
984
985        # We should have
986        # IsZero( PreCompose( PreCompose( KernelEmb( emb_new_source ), phi_new ), emb_new_target ) )
987        # to call CompleteKernelSquare. But since emb_new_source maps from a free module and not from
988        # SubmoduleGeneratedByHomogeneousPart( j, F_source ) the kernel is too big.
989        # We could compute the relations in Source( emb_new_source ). This would imply a costly syzygy
990        # computation, which i would like to circumwent. So CompleteKernelSquare does not yield a
991        # well defined result, but the final result is well defined
992        Assert( 5, IsZero( PreCompose( PreCompose( KernelEmb( emb_new_source ), phi_new ), emb_new_target ) ) );
993        phi := DiagonalMorphism( phi_new, phi );
994        Assert( 5, IsZero( PreCompose( PreCompose( KernelEmb( epi_source ), phi), epi_target ) ) );
995        phi := CompleteKernelSquare( epi_source, phi, epi_target );
996
997    od;
998
999    return phi;
1000
1001end );
1002
1003InstallMethod( HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing,
1004        "for homalg cocomplexes over graded rings",
1005        [ IsHomalgComplex, IsInt, IsInt ],
1006
1007  function( C, min, max )
1008    local HC, j;
1009
1010    HC := HomalgCocomplex( HomogeneousPartOverCoefficientsRing( min, CertainObject( C, min ) ), min );
1011    for j in [ min + 1 .. max ] do
1012        Add( HC, HomogeneousPartOverCoefficientsRing( j, CertainObject( C, j ) ) );
1013    od;
1014
1015    return HC;
1016
1017end );
1018
1019InstallMethod( HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing,
1020        "for homalg cocomplexes over graded rings",
1021        [ IsHomalgChainMorphism, IsInt, IsInt ],
1022
1023  function( C, min, max )
1024    local HC, j, A, B;
1025
1026      A := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( Source( C ), min, max );
1027      B := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( Range( C ), min, max );
1028
1029      HC := HomalgChainMorphism( HomogeneousPartOverCoefficientsRing( min, CertainMorphism( C, min ) ), A, B, min );
1030      for j in [ min + 1 .. max ] do
1031          Add( HC, HomogeneousPartOverCoefficientsRing( j, CertainMorphism( C, j ) ) );
1032      od;
1033
1034      return HC;
1035
1036end );
1037
1038InstallMethod( CompleteKernelSquareByDualization,
1039        "for homalg cocomplexes over graded rings",
1040        [ IsMapOfGradedModulesRep, IsMapOfGradedModulesRep, IsMapOfGradedModulesRep ],
1041
1042  function( alpha2, phi, beta2 )
1043    local A, alpha, id1, id2;
1044
1045      A := HomalgRing( phi );
1046
1047      if not ( HasIsFree( UnderlyingModule( Range( alpha2 ) ) ) and IsFree( UnderlyingModule( Range( alpha2 ) ) ) ) or
1048         not ( HasIsFree( UnderlyingModule( Range( beta2 ) ) ) and IsFree( UnderlyingModule( Range( beta2 ) ) ) ) or
1049         not ( HasIsFree( UnderlyingModule( Source( phi ) ) ) and IsFree( UnderlyingModule( Range( phi ) ) ) ) or
1050         not ( HasIsFree( UnderlyingModule( Range( phi ) ) ) and IsFree( UnderlyingModule( Range( phi ) ) ) ) then
1051          Error( "expect all graded modules to be graded free" );
1052      fi;
1053
1054      alpha := CompleteImageSquare(
1055          GradedHom( beta2, A ),
1056          GradedHom( phi, A ),
1057          GradedHom( alpha2, A )
1058          );
1059      alpha := GradedHom( alpha, A );
1060      Assert( 3, IsMorphism( alpha ) );
1061      SetIsMorphism( alpha, true );
1062      id1 := NatTrIdToHomHom_R( Range( alpha2 ) );
1063      Assert( 3, IsIsomorphism( id1 ) );
1064      SetIsIsomorphism( id1, true );
1065      UpdateObjectsByMorphism( id1 );
1066      id2 := NatTrIdToHomHom_R( Range( beta2 ) );
1067      Assert( 3, IsIsomorphism( id2 ) );
1068      SetIsIsomorphism( id2, true );
1069      UpdateObjectsByMorphism( id2 );
1070
1071      return PreCompose( PreCompose( id1, alpha ), id2^(-1) );
1072
1073end );
1074
1075InstallMethod( SetNaturalMapFromExteriorComplexToRightAdjointForModulesOfGlobalSections,
1076        "for homalg cocomplexes over graded rings",
1077        [ IsHomalgComplex, IsGradedModuleRep ],
1078
1079  function( lin_tate, M )
1080    local truncation_bound, reg, RM, object, alpha, beta, jj, j;
1081
1082    truncation_bound := LowestDegree( lin_tate );
1083
1084    reg := Maximum( HighestDegree( lin_tate ), CastelnuovoMumfordRegularity( M ) );
1085
1086    RM := KoszulRightAdjoint( M, truncation_bound, reg );
1087
1088    object := CertainObject( lin_tate, reg );
1089
1090    alpha := TheIdentityMorphism( object );
1091
1092    beta := HomalgChainMorphism( alpha, lin_tate, RM, reg );
1093
1094    for jj in [ truncation_bound + 1 .. reg ] do
1095        j := reg + truncation_bound - jj;
1096
1097        alpha := CompleteImageSquare( CertainMorphism( lin_tate, j ), alpha, CertainMorphism( RM, j ) );
1098
1099        Add( alpha, beta );
1100
1101    od;
1102
1103    SetNaturalMapFromExteriorComplexToRightAdjoint( lin_tate, beta );
1104
1105end );
1106
1107# Constructs a morphism between two modules F_source and F_target from the cochain map lin_tate
1108# We begin by constructing the map from F_source_{>=reg}=SubmoduleGeneratedByHomogeneousPart(reg,F_source)
1109# to F_target_{>=reg}=SubmoduleGeneratedByHomogeneousPart(reg,F_target).
1110# This map can be directly read of from the morphism in lin_tate at degree reg.
1111# Now we inductively construct maps from the submodules generated by a certain degree of F_source and F_target.
1112# Since F_{>=j} = F_{>=j+1} \oplus <F_j> we have the map starting from the direct sum and finally
1113# also from the factor of this direct sum.
1114InstallGlobalFunction( _Functor_LinearFreeComplexOverExteriorAlgebraToModule_OnGradedMaps,
1115  function( F_source, F_target, arg_before_pos, lin_tate, arg_behind_pos )
1116    local reg_sheaf, lower_bound, A, S, j, object, jj, RF_source, RF_target,
1117          lin_tate_source, lin_tate_target, nat_source, nat_target, alpha,
1118          id1, id2, Hnat_source, Hnat_target, phi, H_source, H_target, phi_source, phi_target, psi;
1119
1120      reg_sheaf := arg_before_pos[1];
1121
1122      lower_bound := LowestDegree( lin_tate );
1123
1124      A := HomalgRing( lin_tate );
1125      S := HomalgRing( F_source );
1126
1127      RF_source := KoszulRightAdjoint( F_source, lower_bound, reg_sheaf );
1128      RF_target := KoszulRightAdjoint( F_target, lower_bound, reg_sheaf );
1129
1130      lin_tate_source := Source( lin_tate );
1131      lin_tate_target := Range( lin_tate );
1132
1133      if not HasNaturalMapFromExteriorComplexToRightAdjoint( lin_tate_source ) then
1134          SetNaturalMapFromExteriorComplexToRightAdjointForModulesOfGlobalSections( lin_tate_source, F_source );
1135      fi;
1136      if not HasNaturalMapFromExteriorComplexToRightAdjoint( lin_tate_target ) then
1137          SetNaturalMapFromExteriorComplexToRightAdjointForModulesOfGlobalSections( lin_tate_target, F_target );
1138      fi;
1139
1140      nat_source := NaturalMapFromExteriorComplexToRightAdjoint( lin_tate_source );
1141      nat_target := NaturalMapFromExteriorComplexToRightAdjoint( lin_tate_target );
1142
1143      Hnat_source := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( nat_source, lower_bound, reg_sheaf );
1144      Hnat_target := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( nat_target, lower_bound, reg_sheaf );
1145
1146      for jj in [ lower_bound .. reg_sheaf ] do
1147          j := reg_sheaf + lower_bound - jj;
1148
1149          phi := CertainMorphism( lin_tate, j );
1150
1151          phi_source := MapFromHomogeneousPartofModuleToHomogeneousPartOfKoszulRightAdjoint( j, F_source );
1152          phi_source := PreCompose( phi_source, CertainMorphism( Hnat_source, j )^(-1) );
1153
1154          phi_target := MapFromHomogeneousPartofModuleToHomogeneousPartOfKoszulRightAdjoint( j, F_target );
1155          phi_target := PreCompose( phi_target, CertainMorphism( Hnat_target, j )^(-1) );
1156
1157          phi := HomogeneousPartOverCoefficientsRing( j, phi );
1158
1159          H_source := HomogeneousPartOverCoefficientsRing( j, F_source );
1160          H_target := HomogeneousPartOverCoefficientsRing( j, F_target );
1161
1162          phi := CompleteImageSquare( phi_source, phi, phi_target );
1163
1164          phi := S * phi;
1165
1166          if j = reg_sheaf then
1167
1168              psi := HomalgChainMorphism( phi, HomalgCocomplex( Source( phi ), reg_sheaf ), HomalgCocomplex( Range( phi ), reg_sheaf ), reg_sheaf );
1169
1170          else
1171
1172              Add( Source( phi ), Source( psi ) );
1173              Add( Range( phi ), Range( psi ) );
1174              Add( phi, psi );
1175
1176          fi;
1177
1178      od;
1179
1180      return ConstructMorphismFromLayers( F_source, F_target, psi );
1181
1182end );
1183
1184InstallValue( Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules,
1185        CreateHomalgFunctor(
1186                [ "name", "LinearFreeComplexOverExteriorAlgebraToModule" ],
1187                [ "category", HOMALG_GRADED_MODULES.category ],
1188                [ "operation", "LinearFreeComplexOverExteriorAlgebraToModule" ],
1189                [ "number_of_arguments", 1 ],
1190                [ "0", [ IsInt ] ],
1191                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], [ IsHomalgComplex, IsHomalgChainMorphism ] ] ],
1192                [ "OnObjects", _Functor_LinearFreeComplexOverExteriorAlgebraToModule_OnGradedModules ],
1193                [ "OnMorphisms", _Functor_LinearFreeComplexOverExteriorAlgebraToModule_OnGradedMaps ],
1194                [ "CompareArgumentsForFunctorObj", CompareArgumentsForLinearFreeComplexOverExteriorAlgebraToModuleOnObjects ],
1195                [ "MorphismConstructor", HOMALG_GRADED_MODULES.category.MorphismConstructor ]
1196                )
1197        );
1198
1199Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
1200
1201Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
1202
1203InstallFunctor( Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules );
1204
1205##
1206## ModuleOfGlobalSectionsTruncatedAtCertainDegree
1207##
1208## (cf. Eisenbud, Floystad, Schreyer: Sheaf Cohomology and Free Resolutions over Exterior Algebras)
1209
1210InstallGlobalFunction( _Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_OnGradedModules,
1211  function( truncation_bound, M )
1212    local V2, map, UM, SOUM, C, reg, tate, B, reg_sheaf, t1, t2, psi, RM, id_old, phi, lin_tate, fit, HM, ii, i, hom_part;
1213
1214      if HasIsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) and HomalgElementToInteger( IsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) ) = truncation_bound then
1215          HM := M;
1216          if truncation_bound = 0 then
1217              V2 := HomogeneousPartOverCoefficientsRing( 0, HM );
1218              map := EmbeddingOfSubmoduleGeneratedByHomogeneousPart( 0, HM );
1219              SetEmbeddingOfSubmoduleGeneratedByHomogeneousPart( V2, map );
1220          fi;
1221          return HM;
1222      fi;
1223
1224      if not IsBound( M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree ) then
1225          M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree := rec( );
1226      elif IsBound( M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) ) then
1227          HM := Range( M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) );
1228          return HM;
1229      fi;
1230
1231      # 0 -> M -> SOUM -> C -> 0
1232      # SOUM is module of global sections
1233      # C does not have a non-trivial artinian submodule
1234      # then M is already a module of global sections
1235      # proof:
1236      #   0 -> M ----> SOUM --> C -> 0
1237      #        |         |      |
1238      #   iota |      Id |      | phi
1239      #       \/        \/     \/
1240      #   0-> HM ----> SOUM -> HC
1241      # Show, that iota is an isomorphism.
1242      # C does not have a non-trivial artinian submodule, so phi is mono.
1243      # The claim follows from the five-lemma.
1244      if HasUnderlyingSubobject( M ) then
1245          UM := UnderlyingSubobject( M );
1246          SOUM := SuperObject( UM );
1247          if IsBound( UM!.map_having_subobject_as_its_image ) and HasIsModuleOfGlobalSectionsTruncatedAtCertainDegree( SOUM ) and
1248             IsInt( HomalgElementToInteger( IsModuleOfGlobalSectionsTruncatedAtCertainDegree( SOUM ) ) ) and HomalgElementToInteger( IsModuleOfGlobalSectionsTruncatedAtCertainDegree( SOUM ) ) = truncation_bound then
1249              C := Cokernel( UM!.map_having_subobject_as_its_image );
1250              if HasIsTorsionFree( C ) and IsTorsionFree( C ) or TrivialArtinianSubmodule( C ) then
1251                  SetIsModuleOfGlobalSectionsTruncatedAtCertainDegree( M, HomalgElementToInteger( IsModuleOfGlobalSectionsTruncatedAtCertainDegree( SOUM ) ) );
1252                  HM := M;
1253                  if truncation_bound = 0 then
1254                      V2 := HomogeneousPartOverCoefficientsRing( 0, HM );
1255                      map := EmbeddingOfSubmoduleGeneratedByHomogeneousPart( 0, HM );
1256                      SetEmbeddingOfSubmoduleGeneratedByHomogeneousPart( V2, map );
1257                  fi;
1258                  M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) := TheIdentityMorphism( M );
1259                  return HM;
1260              fi;
1261          fi;
1262      fi;
1263
1264      # For free modules or modules with a regularity low enough we get the result
1265      # by just truncating the module
1266      if HasIsFree( UnderlyingModule( M ) ) and IsFree( UnderlyingModule( M ) ) or
1267         HomalgElementToInteger( CastelnuovoMumfordRegularity( M ) ) <= truncation_bound then
1268
1269          psi := TruncatedSubmoduleEmbed( truncation_bound, M );
1270
1271          HM := Source( psi );
1272
1273          if truncation_bound = 0 then
1274              V2 := HomogeneousPartOverCoefficientsRing( 0, HM );
1275              map := EmbeddingOfSubmoduleGeneratedByHomogeneousPart( 0, HM );
1276              SetEmbeddingOfSubmoduleGeneratedByHomogeneousPart( V2, map );
1277          fi;
1278
1279          M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) := TheIdentityMorphism( HM );
1280
1281      else
1282
1283          reg := Maximum( truncation_bound, HomalgElementToInteger( CastelnuovoMumfordRegularity( M ) ) );
1284
1285          # in certain cases, when we know that the map to the
1286          # truncated module of global sections is injective,
1287          # we can check by looking at dimensions, whether it is surjective.
1288          # Then, we are done.
1289          if HasIsTorsionFree( M ) and IsTorsionFree( M ) or TrivialArtinianSubmodule( M ) then
1290              lin_tate := LinearStrandOfTateResolution( M, truncation_bound, reg+1 );
1291              fit := true;
1292              for i in [ truncation_bound .. reg+1 ] do
1293                  if not NrGenerators( CertainObject( lin_tate, i ) ) = NrGenerators( HomogeneousPartOverCoefficientsRing( i, M ) ) then
1294                    fit := false;
1295                    break;
1296                  fi;
1297              od;
1298          fi;
1299
1300          if IsBound( fit ) and fit then
1301
1302              psi := TruncatedSubmoduleEmbed( truncation_bound, M );
1303
1304              HM := Source( psi );
1305
1306              if truncation_bound = 0 then
1307                  V2 := HomogeneousPartOverCoefficientsRing( 0, HM );
1308                  map := EmbeddingOfSubmoduleGeneratedByHomogeneousPart( 0, HM );
1309                  SetEmbeddingOfSubmoduleGeneratedByHomogeneousPart( V2, map );
1310              fi;
1311
1312              M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) := TheIdentityMorphism( HM );
1313
1314          # the generic (expensive!) case.
1315          else
1316
1317              lin_tate := LinearStrandOfTateResolution( M, truncation_bound, reg+1 );
1318              reg_sheaf := HomalgElementToInteger( lin_tate!.regularity );
1319
1320              HM := LinearFreeComplexOverExteriorAlgebraToModule( reg_sheaf, lin_tate );
1321
1322              Assert( 5, HomalgElementToInteger( CastelnuovoMumfordRegularity( HM ) ) = reg_sheaf );
1323              SetCastelnuovoMumfordRegularity( HM, reg_sheaf );
1324
1325          fi;
1326
1327      fi;
1328
1329      SetIsModuleOfGlobalSectionsTruncatedAtCertainDegree( HM, truncation_bound );
1330
1331      SetTrivialArtinianSubmodule( HM, true );
1332
1333      if HasIsZero( HM ) then
1334          SetIsArtinian( M, IsZero( HM ) );
1335      fi;
1336
1337      if truncation_bound = 0 then
1338          Assert( 0, HasEmbeddingOfSubmoduleGeneratedByHomogeneousPart( HomogeneousPartOverCoefficientsRing( 0, HM ) ) );
1339      fi;
1340
1341      return HM;
1342
1343end );
1344
1345##
1346InstallGlobalFunction( _Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_OnGradedMaps,
1347  function( F_source, F_target, arg_before_pos, mor, arg_behind_pos )
1348      local truncation_bound, source, target, nat_source, nat_target, reg, lin_tate, reg_sheaf, H_mor;
1349
1350      if IsIdenticalObj( Source( mor ), F_source ) and IsIdenticalObj( Range( mor ), F_target ) then
1351          return mor;
1352      fi;
1353
1354      if not Length( arg_before_pos ) = 1 and IsInt( HomalgElementToInteger( arg_before_pos[1] ) ) then
1355          Error( "expected a bound for the truncation" );
1356      else
1357          truncation_bound := HomalgElementToInteger( arg_before_pos[1] );
1358      fi;
1359
1360      source := Source( mor );
1361      target := Range( mor );
1362
1363      if IsBound( source!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree )
1364         and IsBound( source!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) ) then
1365          nat_source := source!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound);
1366      else
1367          nat_source := fail;
1368      fi;
1369      if IsBound( target!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree )
1370         and IsBound( target!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) ) then
1371          nat_target := target!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound);
1372      else
1373          nat_target := fail;
1374      fi;
1375      if IsIdenticalObj( source, F_source ) and
1376         nat_target <> fail then
1377          return PreCompose(
1378              mor / TruncatedSubmoduleEmbed( truncation_bound, target ),
1379              nat_target );
1380      fi;
1381
1382      if nat_source <> fail and
1383         HasIsEpimorphism( nat_source ) and
1384         IsEpimorphism( nat_source ) and
1385         IsIdenticalObj( target, F_target ) then
1386          H_mor := PreDivide(
1387             nat_source,
1388             PreCompose( TruncatedSubmoduleEmbed( truncation_bound, source ), mor ) );
1389          return H_mor;
1390      fi;
1391
1392      if nat_source <> fail and
1393         HasIsEpimorphism( nat_source ) and
1394         IsEpimorphism( nat_source ) and
1395         nat_target <> fail then
1396          H_mor := CompleteKernelSquare(
1397              nat_source,
1398              TruncatedSubmodule( truncation_bound, mor ),
1399              nat_target );
1400          return H_mor;
1401      fi;
1402
1403      reg := Maximum( truncation_bound, HomalgElementToInteger( CastelnuovoMumfordRegularity( mor ) ) );
1404
1405      lin_tate := LinearStrandOfTateResolution( mor, truncation_bound, reg+1 );
1406
1407      reg_sheaf := Maximum( truncation_bound, HomalgElementToInteger( CastelnuovoMumfordRegularity( F_source ) ), HomalgElementToInteger( CastelnuovoMumfordRegularity( F_target ) ) );
1408
1409      # setting these functors is vital, since ModuleOfGlobalSections on object does not compute with
1410      # LinearFreeComplexOverExteriorAlgebraToModule in every case, but we want to have identical objects
1411      if fail = GetFunctorObjCachedValue( Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules, [ reg_sheaf, Source( lin_tate ) ] ) then
1412          SetFunctorObjCachedValue( Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules, [ reg_sheaf, Source( lin_tate ) ], ModuleOfGlobalSectionsTruncatedAtCertainDegree( truncation_bound, Source( mor ) ) );
1413      fi;
1414      if fail = GetFunctorObjCachedValue( Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules, [ reg_sheaf, Range( lin_tate ) ] ) then
1415          SetFunctorObjCachedValue( Functor_LinearFreeComplexOverExteriorAlgebraToModule_ForGradedModules, [ reg_sheaf, Range( lin_tate ) ], ModuleOfGlobalSectionsTruncatedAtCertainDegree( truncation_bound, Range( mor ) ) );
1416      fi;
1417
1418      H_mor := LinearFreeComplexOverExteriorAlgebraToModule( reg_sheaf, lin_tate );
1419
1420      if HasIsMorphism( mor ) and IsMorphism( mor ) then
1421          SetIsMorphism( H_mor, true );
1422      fi;
1423      if HasIsMonomorphism( mor ) and IsMonomorphism( mor ) then
1424          SetIsMonomorphism( H_mor, true );
1425      fi;
1426
1427      return H_mor;
1428
1429end );
1430
1431##
1432## We create a map by following the layers from
1433## T1) the homogeneous layers of M to
1434## T2) the homogenous parts of coefficients rings in R(M) to
1435## T3) the linear strand of the Tate resolution of M (we possibly need to do CompleteImageSquare here to get down from the regularity of the module to the regularity of the sheaf) to
1436## T4) the homogenous parts of coefficients rings in R(Gamma(M)) (we possibly need to do CompleteKernelSquare here to get back up from the regularity of the sheaf to the regularity of the module) to
1437## T5) the homogeneous layers of Gamma(M)
1438##
1439InstallMethod( NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree,
1440        "for integers and homalg graded modules",
1441        [ IsInt, IsGradedModuleRep ],
1442
1443  function( truncation_bound, M )
1444    local S, A, regM, HM, regHM, T1, i, RM, T2, t1, linTM, T3, tau2, ii, t2, RHM, T4, T5, tau3, alpha, id1, id2, t3, t4, phi;
1445
1446    if not IsBound( M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree ) then
1447        M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree := rec( );
1448    elif IsBound( M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) ) then
1449        return M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound);
1450    fi;
1451
1452    if HasIsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) and IsInt( IsModuleOfGlobalSectionsTruncatedAtCertainDegree( M ) ) then
1453        return TheIdentityMorphism( M );
1454    fi;
1455
1456    S := HomalgRing( M );
1457
1458    A := KoszulDualRing( S );
1459
1460    regM := Maximum( truncation_bound, CastelnuovoMumfordRegularity( M ) );
1461
1462    HM := ModuleOfGlobalSectionsTruncatedAtCertainDegree( truncation_bound, M ); #This might set NaturalMapToModuleOfGlobalSections as a side effect
1463
1464    # generating the module might generate the map naturally.
1465    if IsBound( M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) ) then
1466        return M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound);
1467    fi;
1468
1469    regHM := CastelnuovoMumfordRegularity( HM );
1470
1471    T1 := HomalgCocomplex( HomogeneousPartOverCoefficientsRing( truncation_bound, M ), truncation_bound );
1472    for i in [ truncation_bound + 1 .. regM +1 ] do
1473        Add( T1, HomogeneousPartOverCoefficientsRing( i, M ) );
1474    od;
1475
1476    RM := KoszulRightAdjoint( M, truncation_bound, regM + 1 );
1477    T2 := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( RM, truncation_bound, regM + 1 );
1478
1479    t1 := HomalgChainMorphism( MapFromHomogeneousPartofModuleToHomogeneousPartOfKoszulRightAdjoint( truncation_bound, M ), T1, T2, truncation_bound );
1480    for i in [ truncation_bound + 1 .. regM +1 ] do
1481        Add( t1, MapFromHomogeneousPartofModuleToHomogeneousPartOfKoszulRightAdjoint( i, M ) );
1482    od;
1483    Assert( 3, IsMorphism( t1 ) );
1484    SetIsMorphism( t1, true );
1485
1486    linTM := LinearStrandOfTateResolution( M, truncation_bound, regM + 1 );
1487    T3 := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( linTM, truncation_bound, regM + 1 );
1488
1489    tau2 := HomalgChainMorphism( TheIdentityMorphism( CertainObject( RM, regM + 1 ) ), RM, linTM, regM + 1 );
1490    for ii in [ truncation_bound .. regM ] do
1491        i := regM + truncation_bound - ii;
1492        Add( CompleteImageSquare( CertainMorphism( RM, i ), LowestDegreeMorphism( tau2 ), CertainMorphism( linTM, i ) ), tau2 );
1493    od;
1494
1495    t2 := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( tau2, truncation_bound, regM + 1 );
1496    Assert( 3, IsMorphism( t2 ) );
1497    SetIsMorphism( t2, true );
1498
1499    RHM := KoszulRightAdjoint( HM, truncation_bound, regM + 1 );
1500    T4 := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( RHM, truncation_bound, regM + 1 );
1501
1502
1503    if not HasNaturalMapFromExteriorComplexToRightAdjoint( linTM ) then
1504        SetNaturalMapFromExteriorComplexToRightAdjointForModulesOfGlobalSections( linTM, M );
1505    fi;
1506    tau3 := NaturalMapFromExteriorComplexToRightAdjoint( linTM );
1507    for i in [ Maximum( DegreesOfChainMorphism( tau3 ) ) + 1 .. regM + 1 ] do
1508        alpha := CompleteKernelSquareByDualization( CertainMorphism( linTM, i - 1 ), HighestDegreeMorphism( tau3 ), CertainMorphism( RHM, i - 1 ) );
1509        Assert( 3, IsIsomorphism( alpha ) );
1510        SetIsIsomorphism( alpha, true );
1511        UpdateObjectsByMorphism( alpha );
1512        if not i in ObjectDegreesOfComplex( Range( tau3 ) ) then
1513            Add( Range( tau3 ), CertainMorphism( RHM, i - 1 ) );
1514        fi;
1515        Add( tau3, alpha );
1516    od;
1517
1518    t3 := HomogeneousPartOfCohomologicalDegreeOverCoefficientsRing( tau3, truncation_bound, regM + 1 );
1519    Assert( 3, IsMorphism( t3 ) );
1520    SetIsMorphism( t3, true );
1521
1522    T5 := HomalgCocomplex( HomogeneousPartOverCoefficientsRing( truncation_bound, HM ), truncation_bound );
1523    for i in [ truncation_bound + 1 .. regM +1 ] do
1524        Add( T5, HomogeneousPartOverCoefficientsRing( i, HM ) );
1525    od;
1526
1527    t4 := HomalgChainMorphism( MapFromHomogeneousPartofModuleToHomogeneousPartOfKoszulRightAdjoint( truncation_bound, HM )^(-1), T4, T5, truncation_bound );
1528    for i in [ truncation_bound + 1 .. regM +1 ] do
1529        Add( t4, MapFromHomogeneousPartofModuleToHomogeneousPartOfKoszulRightAdjoint( i, HM )^(-1) );
1530    od;
1531    Assert( 3, IsMorphism( t4 ) );
1532    SetIsMorphism( t4, true );
1533
1534    phi := PreCompose( PreCompose( t1, t2 ), PreCompose( t3, t4 ) );
1535
1536    phi := ConstructMorphismFromLayers( TruncatedModule( truncation_bound, M ), HM, S * phi );
1537
1538    M!.NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree!.(truncation_bound) := phi;
1539
1540    return phi;
1541
1542end );
1543
1544InstallValue( Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_ForGradedModules,
1545        CreateHomalgFunctor(
1546                [ "name", "ModuleOfGlobalSectionsTruncatedAtCertainDegree" ],
1547                [ "category", HOMALG_GRADED_MODULES.category ],
1548                [ "operation", "ModuleOfGlobalSectionsTruncatedAtCertainDegree" ],
1549                [ "number_of_arguments", 1 ],
1550                [ "0", [ IsInt ] ],
1551                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], HOMALG_GRADED_MODULES.FunctorOn ] ],
1552                [ "OnObjects", _Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_OnGradedModules ],
1553                [ "OnMorphisms", _Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_OnGradedMaps ],
1554                [ "MorphismConstructor", HOMALG_GRADED_MODULES.category.MorphismConstructor ]
1555                )
1556        );
1557
1558Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
1559
1560Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
1561
1562InstallFunctor( Functor_ModuleOfGlobalSectionsTruncatedAtCertainDegree_ForGradedModules );
1563
1564##
1565InstallMethod( ModuleOfGlobalSectionsTruncatedAtCertainDegree,
1566               "for homalg elements",
1567               [ IsHomalgElement, IsHomalgGradedMap ],
1568
1569  function( d, M )
1570
1571    return ModuleOfGlobalSectionsTruncatedAtCertainDegree( HomalgElementToInteger( d ), M );
1572
1573end );
1574
1575##
1576InstallMethod( ModuleOfGlobalSectionsTruncatedAtCertainDegree,
1577               "for homalg elements",
1578               [ IsHomalgElement, IsHomalgGradedModule ],
1579
1580  function( d, M )
1581
1582    return ModuleOfGlobalSectionsTruncatedAtCertainDegree( HomalgElementToInteger( d ), M );
1583
1584end );
1585
1586##
1587InstallMethod( NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree,
1588               "for homalg elements",
1589               [ IsHomalgElement, IsHomalgGradedModule ],
1590
1591  function( d, M )
1592
1593    return NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree( HomalgElementToInteger( d ), M );
1594
1595end );
1596
1597##
1598## ModuleOfGlobalSections
1599##
1600
1601InstallGlobalFunction( _Functor_ModuleOfGlobalSections_OnGradedModules,
1602  function( M )
1603      return ModuleOfGlobalSectionsTruncatedAtCertainDegree( HOMALG_GRADED_MODULES!.LowerTruncationBound, M );
1604end );
1605
1606InstallGlobalFunction( _Functor_ModuleOfGlobalSections_OnGradedMaps,
1607  function( F_source, F_target, arg_before_pos, mor, arg_behind_pos )
1608      return ModuleOfGlobalSectionsTruncatedAtCertainDegree( HOMALG_GRADED_MODULES!.LowerTruncationBound, mor );
1609end );
1610
1611InstallValue( Functor_ModuleOfGlobalSections_ForGradedModules,
1612        CreateHomalgFunctor(
1613                [ "name", "ModuleOfGlobalSections" ],
1614                [ "category", HOMALG_GRADED_MODULES.category ],
1615                [ "operation", "ModuleOfGlobalSections" ],
1616                [ "number_of_arguments", 1 ],
1617                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], HOMALG_GRADED_MODULES.FunctorOn ] ],
1618                [ "OnObjects", _Functor_ModuleOfGlobalSections_OnGradedModules ],
1619                [ "OnMorphisms", _Functor_ModuleOfGlobalSections_OnGradedMaps ],
1620                [ "MorphismConstructor", HOMALG_GRADED_MODULES.category.MorphismConstructor ]
1621                )
1622        );
1623
1624Functor_ModuleOfGlobalSections_ForGradedModules!.ContainerForWeakPointersOnComputedBasicObjects := true;
1625
1626Functor_ModuleOfGlobalSections_ForGradedModules!.ContainerForWeakPointersOnComputedBasicMorphisms := true;
1627
1628InstallFunctor( Functor_ModuleOfGlobalSections_ForGradedModules );
1629
1630##
1631InstallMethod( NaturalMapToModuleOfGlobalSections,
1632        "for homalg graded modules",
1633        [ IsGradedModuleRep ],
1634
1635  function( M )
1636
1637    return NaturalMapToModuleOfGlobalSectionsTruncatedAtCertainDegree( HOMALG_GRADED_MODULES!.LowerTruncationBound, M );
1638
1639end );
1640
1641##
1642InstallMethod( ModuleOfGlobalSections,
1643               "for homalg elements",
1644               [ IsHomalgElement, IsHomalgGradedMap ],
1645
1646  function( d, M )
1647
1648    return ModuleOfGlobalSections( HomalgElementToInteger( d ), M );
1649
1650end );
1651
1652##
1653InstallMethod( ModuleOfGlobalSectionsTruncatedAtCertainDegree,
1654               "for homalg elements",
1655               [ IsHomalgElement, IsHomalgGradedModule ],
1656
1657  function( d, M )
1658
1659    return ModuleOfGlobalSections( HomalgElementToInteger( d ), M );
1660
1661end );
1662
1663##
1664## GuessModuleOfGlobalSectionsFromATateMap
1665##
1666
1667##
1668InstallMethod( GuessModuleOfGlobalSectionsFromATateMap,
1669        "for homalg modules",
1670        [ IsMapOfGradedModulesRep ],
1671
1672  function( phi )
1673
1674    return GuessModuleOfGlobalSectionsFromATateMap( 1, phi );
1675
1676end );
1677
1678InstallGlobalFunction( _Functor_GuessModuleOfGlobalSectionsFromATateMap_OnGradedMaps, ### defines: GuessModuleOfGlobalSectionsFromATateMap (object part)
1679
1680  function( steps, phi )
1681    local A, n, psi, deg, lin_tate, alpha, j, K, tate, i, tate2;
1682
1683    Info( InfoWarning, 1, "GuessModuleOfGlobalSectionsFromATateMap uses a heuristic for efficiency;\nplease check the correctness of the following result\n" );
1684
1685    A := HomalgRing( phi );
1686
1687    n := Length( Indeterminates( A ) );
1688
1689    # go up to the regularity
1690
1691    psi := GradedHom( phi, A );
1692
1693    deg := Minimum( List( DegreesOfGenerators( Source( psi ) ), HomalgElementToInteger ) );
1694
1695    lin_tate := HomalgCocomplex( psi, deg );
1696
1697    alpha := LowestDegreeMorphism( lin_tate );
1698
1699    for j in [ 1 .. Maximum( 1, steps ) ] do
1700
1701        repeat
1702
1703            K := Kernel( alpha );
1704            ByASmallerPresentation( K );
1705            Add( PreCompose( CoveringEpi( K ), KernelEmb( alpha ) ), lin_tate );
1706
1707            alpha := LowestDegreeMorphism( lin_tate );
1708
1709            deg := Minimum( List( DegreesOfGenerators( Source( alpha ) ), HomalgElementToInteger ) );
1710            if deg <> Minimum( ObjectDegreesOfComplex( lin_tate ) ) then
1711                lin_tate := HomalgCocomplex( alpha, deg );
1712            fi;
1713
1714        until Minimum( List( DegreesOfGenerators( Source( alpha ) ), HomalgElementToInteger ) ) = Maximum( List( DegreesOfGenerators( Source( alpha ) ), HomalgElementToInteger ) )
1715          and Minimum( List( DegreesOfGenerators( Range( alpha ) ), HomalgElementToInteger ) ) = Maximum( List( DegreesOfGenerators( Range( alpha ) ), HomalgElementToInteger ) )
1716          and HomalgElementToInteger( DegreesOfGenerators( Range( alpha ) )[1] ) = HomalgElementToInteger( DegreesOfGenerators( Source( alpha ) )[1] ) + 1;
1717
1718    od;
1719
1720    lin_tate := LinearStrand( 0, lin_tate );
1721
1722    tate := GradedHom( lin_tate, A );
1723    tate := A^(-n) * tate;
1724
1725    for i in MorphismDegreesOfComplex( tate ) do
1726        if not IsBound( tate2 ) then
1727            tate2 := HomalgCocomplex( CertainMorphism( tate, i ), -i );
1728        else
1729            Add( CertainMorphism( tate, i ), tate2 );
1730        fi;
1731    od;
1732
1733    # go down to HOMALG_GRADED_MODULES!.LowerTruncationBound
1734
1735    ResolveLinearly( Minimum( List( ObjectDegreesOfComplex( tate2 ), HomalgElementToInteger ) ) - HomalgElementToInteger( HOMALG_GRADED_MODULES!.LowerTruncationBound ), tate2 );
1736
1737    # reconstruct the module
1738
1739    return LinearFreeComplexOverExteriorAlgebraToModule( Maximum( List( ObjectDegreesOfComplex( tate2 ), HomalgElementToInteger ) ) - 1, tate2 );
1740
1741end );
1742
1743InstallValue( Functor_GuessModuleOfGlobalSectionsFromATateMap_ForGradedMaps,
1744        CreateHomalgFunctor(
1745                [ "name", "GuessModuleOfGlobalSectionsFromATateMap" ],
1746                [ "category", HOMALG_GRADED_MODULES.category ],
1747                [ "operation", "GuessModuleOfGlobalSectionsFromATateMap" ],
1748                [ "number_of_arguments", 1 ],
1749                [ "0", [ IsInt ] ],
1750                [ "1", [ [ "covariant", "left adjoint", "distinguished" ], [ IsMapOfGradedModulesRep ] ] ],
1751                [ "OnObjects", _Functor_GuessModuleOfGlobalSectionsFromATateMap_OnGradedMaps ],
1752                [ "MorphismConstructor", HOMALG_MODULES.category.MorphismConstructor ]
1753                )
1754        );
1755
1756Functor_GuessModuleOfGlobalSectionsFromATateMap_ForGradedMaps!.ContainerForWeakPointersOnComputedBasicObjects := true;
1757
1758InstallFunctor( Functor_GuessModuleOfGlobalSectionsFromATateMap_ForGradedMaps );
1759
1760##
1761InstallMethod( GuessModuleOfGlobalSectionsFromATateMap,
1762               "for homalg elements",
1763               [ IsHomalgElement, IsHomalgGradedMap ],
1764
1765  function( d, M )
1766
1767    return GuessModuleOfGlobalSectionsFromATateMap( HomalgElementToInteger( d ), M );
1768
1769end );
1770